cmark-gfm-0.1.8/bench/0000755000000000000000000000000013316270352012633 5ustar0000000000000000cmark-gfm-0.1.8/cbits/0000755000000000000000000000000013442037162012660 5ustar0000000000000000cmark-gfm-0.1.8/test/0000755000000000000000000000000013361532343012534 5ustar0000000000000000cmark-gfm-0.1.8/CMarkGFM.hsc0000644000000000000000000006022313442337105013605 0ustar0000000000000000{-# LANGUAGE CPP, ForeignFunctionInterface, GeneralizedNewtypeDeriving, DeriveGeneric, DeriveDataTypeable, FlexibleContexts #-} module CMarkGFM ( commonmarkToHtml , commonmarkToXml , commonmarkToMan , commonmarkToLaTeX , commonmarkToNode , nodeToHtml , nodeToXml , nodeToMan , nodeToLaTeX , nodeToCommonmark , optSourcePos , optHardBreaks , optSmart , optUnsafe , extStrikethrough , extTable , extAutolink , extTagfilter , Node(..) , NodeType(..) , PosInfo(..) , DelimType(..) , ListType(..) , ListAttributes(..) , Url , Title , Level , Info , TableCellAlignment(..) , CMarkOption , CMarkExtension ) where import Foreign import Foreign.C.Types import Foreign.C.String (CString, withCString) import qualified System.IO.Unsafe as Unsafe import Data.Maybe (fromMaybe) import GHC.Generics (Generic) import Data.Data (Data) import Data.Typeable (Typeable) import Data.Text (Text, empty, snoc) import qualified Data.Text.Foreign as TF import Data.ByteString.Unsafe (unsafePackMallocCString) import Data.Text.Encoding (decodeUtf8) import Control.Applicative ((<$>), (<*>)) #include #include -- | Ensure core extensions are registered. ensurePluginsRegistered :: IO () ensurePluginsRegistered = c_cmark_gfm_core_extensions_ensure_registered -- | Frees a cmark linked list, produced by extsToLlist. freeLlist :: LlistPtr a -> IO () freeLlist = c_cmark_llist_free c_cmark_mem -- | Converts a list of resolved extension pointers to a single cmark -- linked list, which can be passed to functions requiring a list of -- extensions. extsToLlist :: [ExtensionPtr] -> IO (LlistPtr ExtensionPtr) extsToLlist [] = return nullPtr extsToLlist (h:t) = do t' <- extsToLlist t c_cmark_llist_append c_cmark_mem t' (castPtr h) -- | Resolves CMarkExtensions to pointers. resolveExts :: [CMarkExtension] -> IO [ExtensionPtr] resolveExts exts = do ensurePluginsRegistered mapM resolveExt exts where resolveExt ext = do p <- withCString (unCMarkExtension ext) c_cmark_find_syntax_extension if p == nullPtr then fail $ "could not load extension " ++ unCMarkExtension ext else return p -- | Convert CommonMark formatted text to Html, using cmark's -- built-in renderer. commonmarkToHtml :: [CMarkOption] -> [CMarkExtension] -> Text -> Text commonmarkToHtml opts exts = commonmarkToX render_html opts exts Nothing where exts' = Unsafe.unsafePerformIO $ resolveExts exts render_html n o _ = do llist <- extsToLlist exts' r <- c_cmark_render_html n o llist freeLlist llist return r -- | Convert CommonMark formatted text to CommonMark XML, using cmark's -- built-in renderer. commonmarkToXml :: [CMarkOption] -> [CMarkExtension] -> Text -> Text commonmarkToXml opts exts = commonmarkToX render_xml opts exts Nothing where render_xml n o _ = c_cmark_render_xml n o -- | Convert CommonMark formatted text to groff man, using cmark's -- built-in renderer. commonmarkToMan :: [CMarkOption] -> [CMarkExtension] -> Maybe Int -> Text -> Text commonmarkToMan = commonmarkToX c_cmark_render_man -- | Convert CommonMark formatted text to latex, using cmark's -- built-in renderer. commonmarkToLaTeX :: [CMarkOption] -> [CMarkExtension] -> Maybe Int -> Text -> Text commonmarkToLaTeX = commonmarkToX c_cmark_render_latex -- | Convert CommonMark formatted text to a structured 'Node' tree, -- which can be transformed or rendered using Haskell code. commonmarkToNode :: [CMarkOption] -> [CMarkExtension] -> Text -> Node commonmarkToNode opts exts s = Unsafe.unsafePerformIO $ do exts' <- resolveExts exts parser <- c_cmark_parser_new (combineOptions opts) mapM_ (c_cmark_parser_attach_syntax_extension parser) exts' TF.withCStringLen s $! \(ptr, len) -> c_cmark_parser_feed parser ptr len nptr <- c_cmark_parser_finish parser c_cmark_parser_free parser fptr <- newForeignPtr c_cmark_node_free nptr withForeignPtr fptr toNode nodeToHtml :: [CMarkOption] -> [CMarkExtension] -> Node -> Text nodeToHtml opts exts = nodeToX render_html opts Nothing where exts' = Unsafe.unsafePerformIO $ resolveExts exts render_html n o _ = do llist <- extsToLlist exts' r <- c_cmark_render_html n o llist freeLlist llist return r nodeToXml :: [CMarkOption] -> Node -> Text nodeToXml opts = nodeToX render_xml opts Nothing where render_xml n o _ = c_cmark_render_xml n o nodeToMan :: [CMarkOption] -> Maybe Int -> Node -> Text nodeToMan = nodeToX c_cmark_render_man nodeToLaTeX :: [CMarkOption] -> Maybe Int -> Node -> Text nodeToLaTeX = nodeToX c_cmark_render_latex nodeToCommonmark :: [CMarkOption] -> Maybe Int -> Node -> Text nodeToCommonmark = nodeToX c_cmark_render_commonmark type Renderer = NodePtr -> CInt -> Int -> IO CString nodeToX :: Renderer -> [CMarkOption] -> Maybe Int -> Node -> Text nodeToX renderer opts mbWidth node = Unsafe.unsafePerformIO $ do nptr <- fromNode node fptr <- newForeignPtr c_cmark_node_free nptr withForeignPtr fptr $ \ptr -> do cstr <- renderer ptr (combineOptions opts) (fromMaybe 0 mbWidth) decodeUtf8 <$> unsafePackMallocCString cstr commonmarkToX :: Renderer -> [CMarkOption] -> [CMarkExtension] -> Maybe Int -> Text -> Text commonmarkToX renderer opts exts mbWidth s = Unsafe.unsafePerformIO $ TF.withCStringLen s $ \(ptr, len) -> do let opts' = combineOptions opts exts' <- resolveExts exts parser <- c_cmark_parser_new opts' mapM_ (c_cmark_parser_attach_syntax_extension parser) exts' c_cmark_parser_feed parser ptr len nptr <- c_cmark_parser_finish parser c_cmark_parser_free parser fptr <- newForeignPtr c_cmark_node_free nptr withForeignPtr fptr $ \p -> do str <- renderer p opts' (fromMaybe 0 mbWidth) decodeUtf8 <$> unsafePackMallocCString str data ParserPhantom type ParserPtr = Ptr ParserPhantom data NodePhantom type NodePtr = Ptr NodePhantom data LlistPhantom a type LlistPtr a = Ptr (LlistPhantom a) data MemPhantom type MemPtr = Ptr MemPhantom data ExtensionPhantom type ExtensionPtr = Ptr ExtensionPhantom data Node = Node (Maybe PosInfo) NodeType [Node] deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) data DelimType = PERIOD_DELIM | PAREN_DELIM deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) data ListType = BULLET_LIST | ORDERED_LIST deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) data ListAttributes = ListAttributes{ listType :: ListType , listTight :: Bool , listStart :: Int , listDelim :: DelimType } deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) type Url = Text type Title = Text type Level = Int type Info = Text type OnEnter = Text type OnExit = Text data TableCellAlignment = NoAlignment | LeftAligned | CenterAligned | RightAligned deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) data NodeType = DOCUMENT | THEMATIC_BREAK | PARAGRAPH | BLOCK_QUOTE | HTML_BLOCK Text | CUSTOM_BLOCK OnEnter OnExit | CODE_BLOCK Info Text | HEADING Level | LIST ListAttributes | ITEM | TEXT Text | SOFTBREAK | LINEBREAK | HTML_INLINE Text | CUSTOM_INLINE OnEnter OnExit | CODE Text | EMPH | STRONG | LINK Url Title | IMAGE Url Title | STRIKETHROUGH | TABLE [TableCellAlignment] | TABLE_ROW | TABLE_CELL deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) data PosInfo = PosInfo{ startLine :: Int , startColumn :: Int , endLine :: Int , endColumn :: Int } deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) newtype CMarkOption = CMarkOption { unCMarkOption :: CInt } -- | Combine a list of options into a single option, using bitwise or. combineOptions :: [CMarkOption] -> CInt combineOptions = foldr ((.|.) . unCMarkOption) 0 -- | Include a @data-sourcepos@ attribute on block elements. optSourcePos :: CMarkOption optSourcePos = CMarkOption #const CMARK_OPT_SOURCEPOS -- | Render @softbreak@ elements as hard line breaks. optHardBreaks :: CMarkOption optHardBreaks = CMarkOption #const CMARK_OPT_HARDBREAKS -- | Convert straight quotes to curly, @---@ to em-dash, @--@ to en-dash. optSmart :: CMarkOption optSmart = CMarkOption #const CMARK_OPT_SMART -- | Allow rendering of raw HTML and potentially dangerous URLs in links -- and images. optUnsafe :: CMarkOption optUnsafe = CMarkOption #const CMARK_OPT_UNSAFE newtype CMarkExtension = CMarkExtension { unCMarkExtension :: String } extStrikethrough :: CMarkExtension extStrikethrough = CMarkExtension "strikethrough" extTable :: CMarkExtension extTable = CMarkExtension "table" extAutolink :: CMarkExtension extAutolink = CMarkExtension "autolink" extTagfilter :: CMarkExtension extTagfilter = CMarkExtension "tagfilter" ptrToNodeType :: NodePtr -> IO NodeType ptrToNodeType ptr = do nodeType <- c_cmark_node_get_type ptr case nodeType of #const CMARK_NODE_DOCUMENT -> return DOCUMENT #const CMARK_NODE_THEMATIC_BREAK -> return THEMATIC_BREAK #const CMARK_NODE_PARAGRAPH -> return PARAGRAPH #const CMARK_NODE_BLOCK_QUOTE -> return BLOCK_QUOTE #const CMARK_NODE_HTML_BLOCK -> HTML_BLOCK <$> literal #const CMARK_NODE_CUSTOM_BLOCK -> CUSTOM_BLOCK <$> onEnter <*> onExit #const CMARK_NODE_CODE_BLOCK -> CODE_BLOCK <$> info <*> literal #const CMARK_NODE_LIST -> LIST <$> listAttr #const CMARK_NODE_ITEM -> return ITEM #const CMARK_NODE_HEADING -> HEADING <$> level #const CMARK_NODE_EMPH -> return EMPH #const CMARK_NODE_STRONG -> return STRONG #const CMARK_NODE_LINK -> LINK <$> url <*> title #const CMARK_NODE_IMAGE -> IMAGE <$> url <*> title #const CMARK_NODE_TEXT -> TEXT <$> literal #const CMARK_NODE_CODE -> CODE <$> literal #const CMARK_NODE_HTML_INLINE -> HTML_INLINE <$> literal #const CMARK_NODE_CUSTOM_INLINE -> CUSTOM_INLINE <$> onEnter <*> onExit #const CMARK_NODE_SOFTBREAK -> return SOFTBREAK #const CMARK_NODE_LINEBREAK -> return LINEBREAK _ -> if nodeType == fromIntegral (Unsafe.unsafePerformIO $ peek c_CMARK_NODE_STRIKETHROUGH) then return STRIKETHROUGH else if nodeType == fromIntegral (Unsafe.unsafePerformIO $ peek c_CMARK_NODE_TABLE) then TABLE <$> alignments else if nodeType == fromIntegral (Unsafe.unsafePerformIO $ peek c_CMARK_NODE_TABLE_ROW) then return TABLE_ROW else if nodeType == fromIntegral (Unsafe.unsafePerformIO $ peek c_CMARK_NODE_TABLE_CELL) then return TABLE_CELL else error $ "Unknown node type " ++ (show nodeType) where literal = c_cmark_node_get_literal ptr >>= totext level = c_cmark_node_get_heading_level ptr onEnter = c_cmark_node_get_on_enter ptr >>= totext onExit = c_cmark_node_get_on_exit ptr >>= totext listAttr = do listtype <- c_cmark_node_get_list_type ptr listdelim <- c_cmark_node_get_list_delim ptr tight <- c_cmark_node_get_list_tight ptr start <- c_cmark_node_get_list_start ptr return ListAttributes{ listType = case listtype of (#const CMARK_ORDERED_LIST) -> ORDERED_LIST (#const CMARK_BULLET_LIST) -> BULLET_LIST _ -> BULLET_LIST , listDelim = case listdelim of (#const CMARK_PERIOD_DELIM) -> PERIOD_DELIM (#const CMARK_PAREN_DELIM) -> PAREN_DELIM _ -> PERIOD_DELIM , listTight = tight , listStart = start } url = c_cmark_node_get_url ptr >>= totext title = c_cmark_node_get_title ptr >>= totext info = c_cmark_node_get_fence_info ptr >>= totext alignments = do ncols <- c_cmark_gfm_extensions_get_table_columns ptr cols <- c_cmark_gfm_extensions_get_table_alignments ptr mapM (fmap ucharToAlignment . peekElemOff cols) [0..(fromIntegral ncols) - 1] ucharToAlignment (CUChar 108) = LeftAligned ucharToAlignment (CUChar 99) = CenterAligned ucharToAlignment (CUChar 114) = RightAligned ucharToAlignment _ = NoAlignment getPosInfo :: NodePtr -> IO (Maybe PosInfo) getPosInfo ptr = do startline <- c_cmark_node_get_start_line ptr endline <- c_cmark_node_get_end_line ptr startcol <- c_cmark_node_get_start_column ptr endcol <- c_cmark_node_get_end_column ptr if startline + endline + startcol + endcol == 0 then return Nothing else return $ Just PosInfo{ startLine = startline , startColumn = startcol , endLine = endline , endColumn = endcol } toNode :: NodePtr -> IO Node toNode ptr = do let handleNodes ptr' = if ptr' == nullPtr then return [] else do x <- toNode ptr' xs <- c_cmark_node_next ptr' >>= handleNodes return $! (x:xs) nodeType <- ptrToNodeType ptr children <- c_cmark_node_first_child ptr >>= handleNodes posinfo <- getPosInfo ptr return $! Node posinfo nodeType children fromNode :: Node -> IO NodePtr fromNode (Node _ nodeType children) = do node <- case nodeType of DOCUMENT -> c_cmark_node_new (#const CMARK_NODE_DOCUMENT) THEMATIC_BREAK -> c_cmark_node_new (#const CMARK_NODE_THEMATIC_BREAK) PARAGRAPH -> c_cmark_node_new (#const CMARK_NODE_PARAGRAPH) BLOCK_QUOTE -> c_cmark_node_new (#const CMARK_NODE_BLOCK_QUOTE) HTML_BLOCK literal -> do n <- c_cmark_node_new (#const CMARK_NODE_HTML_BLOCK) withtext literal (c_cmark_node_set_literal n) return n CUSTOM_BLOCK onEnter onExit -> do n <- c_cmark_node_new (#const CMARK_NODE_CUSTOM_BLOCK) withtext onEnter (c_cmark_node_set_on_enter n) withtext onExit (c_cmark_node_set_on_exit n) return n CODE_BLOCK info literal -> do n <- c_cmark_node_new (#const CMARK_NODE_CODE_BLOCK) withtext literal (c_cmark_node_set_literal n) withtext info (c_cmark_node_set_fence_info n) return n LIST attr -> do n <- c_cmark_node_new (#const CMARK_NODE_LIST) c_cmark_node_set_list_type n $ case listType attr of ORDERED_LIST -> #const CMARK_ORDERED_LIST BULLET_LIST -> #const CMARK_BULLET_LIST c_cmark_node_set_list_delim n $ case listDelim attr of PERIOD_DELIM -> #const CMARK_PERIOD_DELIM PAREN_DELIM -> #const CMARK_PAREN_DELIM c_cmark_node_set_list_tight n $ listTight attr c_cmark_node_set_list_start n $ listStart attr return n ITEM -> c_cmark_node_new (#const CMARK_NODE_ITEM) HEADING lev -> do n <- c_cmark_node_new (#const CMARK_NODE_HEADING) c_cmark_node_set_heading_level n lev return n EMPH -> c_cmark_node_new (#const CMARK_NODE_EMPH) STRONG -> c_cmark_node_new (#const CMARK_NODE_STRONG) LINK url title -> do n <- c_cmark_node_new (#const CMARK_NODE_LINK) withtext url (c_cmark_node_set_url n) withtext title (c_cmark_node_set_title n) return n IMAGE url title -> do n <- c_cmark_node_new (#const CMARK_NODE_IMAGE) withtext url (c_cmark_node_set_url n) withtext title (c_cmark_node_set_title n) return n TEXT literal -> do n <- c_cmark_node_new (#const CMARK_NODE_TEXT) withtext literal (c_cmark_node_set_literal n) return n CODE literal -> do n <- c_cmark_node_new (#const CMARK_NODE_CODE) withtext literal (c_cmark_node_set_literal n) return n HTML_INLINE literal -> do n <- c_cmark_node_new (#const CMARK_NODE_HTML_INLINE) withtext literal (c_cmark_node_set_literal n) return n CUSTOM_INLINE onEnter onExit -> do n <- c_cmark_node_new (#const CMARK_NODE_CUSTOM_INLINE) withtext onEnter (c_cmark_node_set_on_enter n) withtext onExit (c_cmark_node_set_on_exit n) return n SOFTBREAK -> c_cmark_node_new (#const CMARK_NODE_SOFTBREAK) LINEBREAK -> c_cmark_node_new (#const CMARK_NODE_LINEBREAK) STRIKETHROUGH -> c_cmark_node_new (fromIntegral . Unsafe.unsafePerformIO $ peek c_CMARK_NODE_STRIKETHROUGH) TABLE _ -> error "constructing table not supported" TABLE_ROW -> error "constructing table row not supported" TABLE_CELL -> error "constructing table cell not supported" mapM_ (\child -> fromNode child >>= c_cmark_node_append_child node) children return node totext :: CString -> IO Text totext str | str == nullPtr = return empty | otherwise = TF.peekCStringLen (str, c_strlen str) withtext :: Text -> (CString -> IO a) -> IO a withtext t f = TF.withCStringLen (snoc t '\0') (f . fst) foreign import ccall "string.h strlen" c_strlen :: CString -> Int foreign import ccall "cmark-gfm.h cmark_node_new" c_cmark_node_new :: Int -> IO NodePtr foreign import ccall "cmark-gfm.h cmark_render_html" c_cmark_render_html :: NodePtr -> CInt -> LlistPtr ExtensionPtr -> IO CString foreign import ccall "cmark-gfm.h cmark_render_xml" c_cmark_render_xml :: NodePtr -> CInt -> IO CString foreign import ccall "cmark-gfm.h cmark_render_man" c_cmark_render_man :: NodePtr -> CInt -> Int -> IO CString foreign import ccall "cmark-gfm.h cmark_render_latex" c_cmark_render_latex :: NodePtr -> CInt -> Int -> IO CString foreign import ccall "cmark-gfm.h cmark_render_commonmark" c_cmark_render_commonmark :: NodePtr -> CInt -> Int -> IO CString foreign import ccall "cmark-gfm.h cmark_parser_new" c_cmark_parser_new :: CInt -> IO ParserPtr foreign import ccall "cmark-gfm.h cmark_parser_feed" c_cmark_parser_feed :: ParserPtr -> CString -> Int -> IO () foreign import ccall "cmark-gfm.h cmark_parser_finish" c_cmark_parser_finish :: ParserPtr -> IO NodePtr foreign import ccall "cmark-gfm.h cmark_parser_free" c_cmark_parser_free :: ParserPtr -> IO () foreign import ccall "cmark-gfm.h cmark_node_get_type" c_cmark_node_get_type :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_first_child" c_cmark_node_first_child :: NodePtr -> IO NodePtr foreign import ccall "cmark-gfm.h cmark_node_next" c_cmark_node_next :: NodePtr -> IO NodePtr foreign import ccall "cmark-gfm.h cmark_node_get_literal" c_cmark_node_get_literal :: NodePtr -> IO CString foreign import ccall "cmark-gfm.h cmark_node_get_url" c_cmark_node_get_url :: NodePtr -> IO CString foreign import ccall "cmark-gfm.h cmark_node_get_title" c_cmark_node_get_title :: NodePtr -> IO CString foreign import ccall "cmark-gfm.h cmark_node_get_heading_level" c_cmark_node_get_heading_level :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_list_type" c_cmark_node_get_list_type :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_list_tight" c_cmark_node_get_list_tight :: NodePtr -> IO Bool foreign import ccall "cmark-gfm.h cmark_node_get_list_start" c_cmark_node_get_list_start :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_list_delim" c_cmark_node_get_list_delim :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_fence_info" c_cmark_node_get_fence_info :: NodePtr -> IO CString foreign import ccall "cmark-gfm.h cmark_node_get_start_line" c_cmark_node_get_start_line :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_start_column" c_cmark_node_get_start_column :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_end_line" c_cmark_node_get_end_line :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_end_column" c_cmark_node_get_end_column :: NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_get_on_enter" c_cmark_node_get_on_enter :: NodePtr -> IO CString foreign import ccall "cmark-gfm.h cmark_node_get_on_exit" c_cmark_node_get_on_exit :: NodePtr -> IO CString foreign import ccall "cmark-gfm.h cmark_node_append_child" c_cmark_node_append_child :: NodePtr -> NodePtr -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_literal" c_cmark_node_set_literal :: NodePtr -> CString -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_url" c_cmark_node_set_url :: NodePtr -> CString -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_title" c_cmark_node_set_title :: NodePtr -> CString -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_heading_level" c_cmark_node_set_heading_level :: NodePtr -> Int -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_list_type" c_cmark_node_set_list_type :: NodePtr -> Int -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_list_tight" c_cmark_node_set_list_tight :: NodePtr -> Bool -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_list_start" c_cmark_node_set_list_start :: NodePtr -> Int -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_list_delim" c_cmark_node_set_list_delim :: NodePtr -> Int -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_fence_info" c_cmark_node_set_fence_info :: NodePtr -> CString -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_on_enter" c_cmark_node_set_on_enter :: NodePtr -> CString -> IO Int foreign import ccall "cmark-gfm.h cmark_node_set_on_exit" c_cmark_node_set_on_exit :: NodePtr -> CString -> IO Int foreign import ccall "cmark-gfm.h &cmark_node_free" c_cmark_node_free :: FunPtr (NodePtr -> IO ()) foreign import ccall "cmark-gfm-core-extensions.h cmark_gfm_core_extensions_ensure_registered" c_cmark_gfm_core_extensions_ensure_registered :: IO () foreign import ccall "cmark-gfm-extension_api.h cmark_find_syntax_extension" c_cmark_find_syntax_extension :: CString -> IO ExtensionPtr foreign import ccall "cmark-gfm.h cmark_llist_append" c_cmark_llist_append :: MemPtr -> LlistPtr a -> Ptr () -> IO (LlistPtr a) foreign import ccall "cmark-gfm.h cmark_llist_free" c_cmark_llist_free :: MemPtr -> LlistPtr a -> IO () foreign import ccall "cmark-gfm.h cmark_get_default_mem_allocator" c_cmark_mem :: MemPtr foreign import ccall "cmark-gfm-extension_api.h cmark_parser_attach_syntax_extension" c_cmark_parser_attach_syntax_extension :: ParserPtr -> ExtensionPtr -> IO () foreign import ccall "strikethrough.h &CMARK_NODE_STRIKETHROUGH" c_CMARK_NODE_STRIKETHROUGH :: Ptr #type cmark_node_type foreign import ccall "table.h &CMARK_NODE_TABLE" c_CMARK_NODE_TABLE :: Ptr #type cmark_node_type foreign import ccall "table.h &CMARK_NODE_TABLE_ROW" c_CMARK_NODE_TABLE_ROW :: Ptr #type cmark_node_type foreign import ccall "table.h &CMARK_NODE_TABLE_CELL" c_CMARK_NODE_TABLE_CELL :: Ptr #type cmark_node_type foreign import ccall "cmark-gfm-core-extensions.h cmark_gfm_extensions_get_table_columns" c_cmark_gfm_extensions_get_table_columns :: NodePtr -> IO CUShort foreign import ccall "cmark-gfm-core-extensions.h cmark_gfm_extensions_get_table_alignments" c_cmark_gfm_extensions_get_table_alignments :: NodePtr -> IO (Ptr CUChar) cmark-gfm-0.1.8/cbits/houdini_html_u.c0000644000000000000000000000675613361532163016052 0ustar0000000000000000#include #include #include #include "buffer.h" #include "houdini.h" #include "utf8.h" #include "entities.inc" /* Binary tree lookup code for entities added by JGM */ static const unsigned char *S_lookup(int i, int low, int hi, const unsigned char *s, int len) { int j; int cmp = strncmp((const char *)s, (const char *)cmark_entities[i].entity, len); if (cmp == 0 && cmark_entities[i].entity[len] == 0) { return (const unsigned char *)cmark_entities[i].bytes; } else if (cmp <= 0 && i > low) { j = i - ((i - low) / 2); if (j == i) j -= 1; return S_lookup(j, low, i - 1, s, len); } else if (cmp > 0 && i < hi) { j = i + ((hi - i) / 2); if (j == i) j += 1; return S_lookup(j, i + 1, hi, s, len); } else { return NULL; } } static const unsigned char *S_lookup_entity(const unsigned char *s, int len) { return S_lookup(CMARK_NUM_ENTITIES / 2, 0, CMARK_NUM_ENTITIES - 1, s, len); } bufsize_t houdini_unescape_ent(cmark_strbuf *ob, const uint8_t *src, bufsize_t size) { bufsize_t i = 0; if (size >= 3 && src[0] == '#') { int codepoint = 0; int num_digits = 0; if (_isdigit(src[1])) { for (i = 1; i < size && _isdigit(src[i]); ++i) { codepoint = (codepoint * 10) + (src[i] - '0'); if (codepoint >= 0x110000) { // Keep counting digits but // avoid integer overflow. codepoint = 0x110000; } } num_digits = i - 1; } else if (src[1] == 'x' || src[1] == 'X') { for (i = 2; i < size && _isxdigit(src[i]); ++i) { codepoint = (codepoint * 16) + ((src[i] | 32) % 39 - 9); if (codepoint >= 0x110000) { // Keep counting digits but // avoid integer overflow. codepoint = 0x110000; } } num_digits = i - 2; } if (num_digits >= 1 && num_digits <= 8 && i < size && src[i] == ';') { if (codepoint == 0 || (codepoint >= 0xD800 && codepoint < 0xE000) || codepoint >= 0x110000) { codepoint = 0xFFFD; } cmark_utf8proc_encode_char(codepoint, ob); return i + 1; } } else { if (size > CMARK_ENTITY_MAX_LENGTH) size = CMARK_ENTITY_MAX_LENGTH; for (i = CMARK_ENTITY_MIN_LENGTH; i < size; ++i) { if (src[i] == ' ') break; if (src[i] == ';') { const unsigned char *entity = S_lookup_entity(src, i); if (entity != NULL) { cmark_strbuf_puts(ob, (const char *)entity); return i + 1; } break; } } } return 0; } int houdini_unescape_html(cmark_strbuf *ob, const uint8_t *src, bufsize_t size) { bufsize_t i = 0, org, ent; while (i < size) { org = i; while (i < size && src[i] != '&') i++; if (likely(i > org)) { if (unlikely(org == 0)) { if (i >= size) return 0; cmark_strbuf_grow(ob, HOUDINI_UNESCAPED_SIZE(size)); } cmark_strbuf_put(ob, src + org, i - org); } /* escaping */ if (i >= size) break; i++; ent = houdini_unescape_ent(ob, src + i, size - i); i += ent; /* not really an entity */ if (ent == 0) cmark_strbuf_putc(ob, '&'); } return 1; } void houdini_unescape_html_f(cmark_strbuf *ob, const uint8_t *src, bufsize_t size) { if (!houdini_unescape_html(ob, src, size)) cmark_strbuf_put(ob, src, size); } cmark-gfm-0.1.8/cbits/references.c0000644000000000000000000000223013442034251015136 0ustar0000000000000000#include "cmark-gfm.h" #include "parser.h" #include "references.h" #include "inlines.h" #include "chunk.h" static void reference_free(cmark_map *map, cmark_map_entry *_ref) { cmark_reference *ref = (cmark_reference *)_ref; cmark_mem *mem = map->mem; if (ref != NULL) { mem->free(ref->entry.label); cmark_chunk_free(mem, &ref->url); cmark_chunk_free(mem, &ref->title); mem->free(ref); } } void cmark_reference_create(cmark_map *map, cmark_chunk *label, cmark_chunk *url, cmark_chunk *title) { cmark_reference *ref; unsigned char *reflabel = normalize_map_label(map->mem, label); /* empty reference name, or composed from only whitespace */ if (reflabel == NULL) return; assert(map->sorted == NULL); ref = (cmark_reference *)map->mem->calloc(1, sizeof(*ref)); ref->entry.label = reflabel; ref->url = cmark_clean_url(map->mem, url); ref->title = cmark_clean_title(map->mem, title); ref->entry.age = map->size; ref->entry.next = map->refs; map->refs = (cmark_map_entry *)ref; map->size++; } cmark_map *cmark_reference_map_new(cmark_mem *mem) { return cmark_map_new(mem, reference_free); } cmark-gfm-0.1.8/cbits/utf8.c0000644000000000000000000002361113361532163013716 0ustar0000000000000000#include #include #include #include "cmark_ctype.h" #include "utf8.h" static const int8_t utf8proc_utf8class[256] = { 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, 4, 4, 0, 0, 0, 0, 0, 0, 0, 0}; static void encode_unknown(cmark_strbuf *buf) { static const uint8_t repl[] = {239, 191, 189}; cmark_strbuf_put(buf, repl, 3); } static int utf8proc_charlen(const uint8_t *str, bufsize_t str_len) { int length, i; if (!str_len) return 0; length = utf8proc_utf8class[str[0]]; if (!length) return -1; if (str_len >= 0 && (bufsize_t)length > str_len) return -str_len; for (i = 1; i < length; i++) { if ((str[i] & 0xC0) != 0x80) return -i; } return length; } // Validate a single UTF-8 character according to RFC 3629. static int utf8proc_valid(const uint8_t *str, bufsize_t str_len) { int length = utf8proc_utf8class[str[0]]; if (!length) return -1; if ((bufsize_t)length > str_len) return -str_len; switch (length) { case 2: if ((str[1] & 0xC0) != 0x80) return -1; if (str[0] < 0xC2) { // Overlong return -length; } break; case 3: if ((str[1] & 0xC0) != 0x80) return -1; if ((str[2] & 0xC0) != 0x80) return -2; if (str[0] == 0xE0) { if (str[1] < 0xA0) { // Overlong return -length; } } else if (str[0] == 0xED) { if (str[1] >= 0xA0) { // Surrogate return -length; } } break; case 4: if ((str[1] & 0xC0) != 0x80) return -1; if ((str[2] & 0xC0) != 0x80) return -2; if ((str[3] & 0xC0) != 0x80) return -3; if (str[0] == 0xF0) { if (str[1] < 0x90) { // Overlong return -length; } } else if (str[0] >= 0xF4) { if (str[0] > 0xF4 || str[1] >= 0x90) { // Above 0x10FFFF return -length; } } break; } return length; } void cmark_utf8proc_check(cmark_strbuf *ob, const uint8_t *line, bufsize_t size) { bufsize_t i = 0; while (i < size) { bufsize_t org = i; int charlen = 0; while (i < size) { if (line[i] < 0x80 && line[i] != 0) { i++; } else if (line[i] >= 0x80) { charlen = utf8proc_valid(line + i, size - i); if (charlen < 0) { charlen = -charlen; break; } i += charlen; } else if (line[i] == 0) { // ASCII NUL is technically valid but rejected // for security reasons. charlen = 1; break; } } if (i > org) { cmark_strbuf_put(ob, line + org, i - org); } if (i >= size) { break; } else { // Invalid UTF-8 encode_unknown(ob); i += charlen; } } } int cmark_utf8proc_iterate(const uint8_t *str, bufsize_t str_len, int32_t *dst) { int length; int32_t uc = -1; *dst = -1; length = utf8proc_charlen(str, str_len); if (length < 0) return -1; switch (length) { case 1: uc = str[0]; break; case 2: uc = ((str[0] & 0x1F) << 6) + (str[1] & 0x3F); if (uc < 0x80) uc = -1; break; case 3: uc = ((str[0] & 0x0F) << 12) + ((str[1] & 0x3F) << 6) + (str[2] & 0x3F); if (uc < 0x800 || (uc >= 0xD800 && uc < 0xE000)) uc = -1; break; case 4: uc = ((str[0] & 0x07) << 18) + ((str[1] & 0x3F) << 12) + ((str[2] & 0x3F) << 6) + (str[3] & 0x3F); if (uc < 0x10000 || uc >= 0x110000) uc = -1; break; } if (uc < 0) return -1; *dst = uc; return length; } void cmark_utf8proc_encode_char(int32_t uc, cmark_strbuf *buf) { uint8_t dst[4]; bufsize_t len = 0; assert(uc >= 0); if (uc < 0x80) { dst[0] = (uint8_t)(uc); len = 1; } else if (uc < 0x800) { dst[0] = (uint8_t)(0xC0 + (uc >> 6)); dst[1] = 0x80 + (uc & 0x3F); len = 2; } else if (uc == 0xFFFF) { dst[0] = 0xFF; len = 1; } else if (uc == 0xFFFE) { dst[0] = 0xFE; len = 1; } else if (uc < 0x10000) { dst[0] = (uint8_t)(0xE0 + (uc >> 12)); dst[1] = 0x80 + ((uc >> 6) & 0x3F); dst[2] = 0x80 + (uc & 0x3F); len = 3; } else if (uc < 0x110000) { dst[0] = (uint8_t)(0xF0 + (uc >> 18)); dst[1] = 0x80 + ((uc >> 12) & 0x3F); dst[2] = 0x80 + ((uc >> 6) & 0x3F); dst[3] = 0x80 + (uc & 0x3F); len = 4; } else { encode_unknown(buf); return; } cmark_strbuf_put(buf, dst, len); } void cmark_utf8proc_case_fold(cmark_strbuf *dest, const uint8_t *str, bufsize_t len) { int32_t c; #define bufpush(x) cmark_utf8proc_encode_char(x, dest) while (len > 0) { bufsize_t char_len = cmark_utf8proc_iterate(str, len, &c); if (char_len >= 0) { #include "case_fold_switch.inc" } else { encode_unknown(dest); char_len = -char_len; } str += char_len; len -= char_len; } } // matches anything in the Zs class, plus LF, CR, TAB, FF. int cmark_utf8proc_is_space(int32_t uc) { return (uc == 9 || uc == 10 || uc == 12 || uc == 13 || uc == 32 || uc == 160 || uc == 5760 || (uc >= 8192 && uc <= 8202) || uc == 8239 || uc == 8287 || uc == 12288); } // matches anything in the P[cdefios] classes. int cmark_utf8proc_is_punctuation(int32_t uc) { return ( (uc < 128 && cmark_ispunct((char)uc)) || uc == 161 || uc == 167 || uc == 171 || uc == 182 || uc == 183 || uc == 187 || uc == 191 || uc == 894 || uc == 903 || (uc >= 1370 && uc <= 1375) || uc == 1417 || uc == 1418 || uc == 1470 || uc == 1472 || uc == 1475 || uc == 1478 || uc == 1523 || uc == 1524 || uc == 1545 || uc == 1546 || uc == 1548 || uc == 1549 || uc == 1563 || uc == 1566 || uc == 1567 || (uc >= 1642 && uc <= 1645) || uc == 1748 || (uc >= 1792 && uc <= 1805) || (uc >= 2039 && uc <= 2041) || (uc >= 2096 && uc <= 2110) || uc == 2142 || uc == 2404 || uc == 2405 || uc == 2416 || uc == 2800 || uc == 3572 || uc == 3663 || uc == 3674 || uc == 3675 || (uc >= 3844 && uc <= 3858) || uc == 3860 || (uc >= 3898 && uc <= 3901) || uc == 3973 || (uc >= 4048 && uc <= 4052) || uc == 4057 || uc == 4058 || (uc >= 4170 && uc <= 4175) || uc == 4347 || (uc >= 4960 && uc <= 4968) || uc == 5120 || uc == 5741 || uc == 5742 || uc == 5787 || uc == 5788 || (uc >= 5867 && uc <= 5869) || uc == 5941 || uc == 5942 || (uc >= 6100 && uc <= 6102) || (uc >= 6104 && uc <= 6106) || (uc >= 6144 && uc <= 6154) || uc == 6468 || uc == 6469 || uc == 6686 || uc == 6687 || (uc >= 6816 && uc <= 6822) || (uc >= 6824 && uc <= 6829) || (uc >= 7002 && uc <= 7008) || (uc >= 7164 && uc <= 7167) || (uc >= 7227 && uc <= 7231) || uc == 7294 || uc == 7295 || (uc >= 7360 && uc <= 7367) || uc == 7379 || (uc >= 8208 && uc <= 8231) || (uc >= 8240 && uc <= 8259) || (uc >= 8261 && uc <= 8273) || (uc >= 8275 && uc <= 8286) || uc == 8317 || uc == 8318 || uc == 8333 || uc == 8334 || (uc >= 8968 && uc <= 8971) || uc == 9001 || uc == 9002 || (uc >= 10088 && uc <= 10101) || uc == 10181 || uc == 10182 || (uc >= 10214 && uc <= 10223) || (uc >= 10627 && uc <= 10648) || (uc >= 10712 && uc <= 10715) || uc == 10748 || uc == 10749 || (uc >= 11513 && uc <= 11516) || uc == 11518 || uc == 11519 || uc == 11632 || (uc >= 11776 && uc <= 11822) || (uc >= 11824 && uc <= 11842) || (uc >= 12289 && uc <= 12291) || (uc >= 12296 && uc <= 12305) || (uc >= 12308 && uc <= 12319) || uc == 12336 || uc == 12349 || uc == 12448 || uc == 12539 || uc == 42238 || uc == 42239 || (uc >= 42509 && uc <= 42511) || uc == 42611 || uc == 42622 || (uc >= 42738 && uc <= 42743) || (uc >= 43124 && uc <= 43127) || uc == 43214 || uc == 43215 || (uc >= 43256 && uc <= 43258) || uc == 43310 || uc == 43311 || uc == 43359 || (uc >= 43457 && uc <= 43469) || uc == 43486 || uc == 43487 || (uc >= 43612 && uc <= 43615) || uc == 43742 || uc == 43743 || uc == 43760 || uc == 43761 || uc == 44011 || uc == 64830 || uc == 64831 || (uc >= 65040 && uc <= 65049) || (uc >= 65072 && uc <= 65106) || (uc >= 65108 && uc <= 65121) || uc == 65123 || uc == 65128 || uc == 65130 || uc == 65131 || (uc >= 65281 && uc <= 65283) || (uc >= 65285 && uc <= 65290) || (uc >= 65292 && uc <= 65295) || uc == 65306 || uc == 65307 || uc == 65311 || uc == 65312 || (uc >= 65339 && uc <= 65341) || uc == 65343 || uc == 65371 || uc == 65373 || (uc >= 65375 && uc <= 65381) || (uc >= 65792 && uc <= 65794) || uc == 66463 || uc == 66512 || uc == 66927 || uc == 67671 || uc == 67871 || uc == 67903 || (uc >= 68176 && uc <= 68184) || uc == 68223 || (uc >= 68336 && uc <= 68342) || (uc >= 68409 && uc <= 68415) || (uc >= 68505 && uc <= 68508) || (uc >= 69703 && uc <= 69709) || uc == 69819 || uc == 69820 || (uc >= 69822 && uc <= 69825) || (uc >= 69952 && uc <= 69955) || uc == 70004 || uc == 70005 || (uc >= 70085 && uc <= 70088) || uc == 70093 || (uc >= 70200 && uc <= 70205) || uc == 70854 || (uc >= 71105 && uc <= 71113) || (uc >= 71233 && uc <= 71235) || (uc >= 74864 && uc <= 74868) || uc == 92782 || uc == 92783 || uc == 92917 || (uc >= 92983 && uc <= 92987) || uc == 92996 || uc == 113823); } cmark-gfm-0.1.8/cbits/inlines.c0000644000000000000000000014206113442037162014471 0ustar0000000000000000#include #include #include #include "cmark_ctype.h" #include "config.h" #include "node.h" #include "parser.h" #include "references.h" #include "cmark-gfm.h" #include "houdini.h" #include "utf8.h" #include "scanners.h" #include "inlines.h" #include "syntax_extension.h" static const char *EMDASH = "\xE2\x80\x94"; static const char *ENDASH = "\xE2\x80\x93"; static const char *ELLIPSES = "\xE2\x80\xA6"; static const char *LEFTDOUBLEQUOTE = "\xE2\x80\x9C"; static const char *RIGHTDOUBLEQUOTE = "\xE2\x80\x9D"; static const char *LEFTSINGLEQUOTE = "\xE2\x80\x98"; static const char *RIGHTSINGLEQUOTE = "\xE2\x80\x99"; // Macros for creating various kinds of simple. #define make_str(subj, sc, ec, s) make_literal(subj, CMARK_NODE_TEXT, sc, ec, s) #define make_code(subj, sc, ec, s) make_literal(subj, CMARK_NODE_CODE, sc, ec, s) #define make_raw_html(subj, sc, ec, s) make_literal(subj, CMARK_NODE_HTML_INLINE, sc, ec, s) #define make_linebreak(mem) make_simple(mem, CMARK_NODE_LINEBREAK) #define make_softbreak(mem) make_simple(mem, CMARK_NODE_SOFTBREAK) #define make_emph(mem) make_simple(mem, CMARK_NODE_EMPH) #define make_strong(mem) make_simple(mem, CMARK_NODE_STRONG) #define MAXBACKTICKS 80 typedef struct bracket { struct bracket *previous; struct delimiter *previous_delimiter; cmark_node *inl_text; bufsize_t position; bool image; bool active; bool bracket_after; } bracket; typedef struct subject{ cmark_mem *mem; cmark_chunk input; int line; bufsize_t pos; int block_offset; int column_offset; cmark_map *refmap; delimiter *last_delim; bracket *last_bracket; bufsize_t backticks[MAXBACKTICKS + 1]; bool scanned_for_backticks; } subject; // Extensions may populate this. static int8_t SKIP_CHARS[256]; static CMARK_INLINE bool S_is_line_end_char(char c) { return (c == '\n' || c == '\r'); } static delimiter *S_insert_emph(subject *subj, delimiter *opener, delimiter *closer); static int parse_inline(cmark_parser *parser, subject *subj, cmark_node *parent, int options); static void subject_from_buf(cmark_mem *mem, int line_number, int block_offset, subject *e, cmark_chunk *buffer, cmark_map *refmap); static bufsize_t subject_find_special_char(subject *subj, int options); // Create an inline with a literal string value. static CMARK_INLINE cmark_node *make_literal(subject *subj, cmark_node_type t, int start_column, int end_column, cmark_chunk s) { cmark_node *e = (cmark_node *)subj->mem->calloc(1, sizeof(*e)); cmark_strbuf_init(subj->mem, &e->content, 0); e->type = (uint16_t)t; e->as.literal = s; e->start_line = e->end_line = subj->line; // columns are 1 based. e->start_column = start_column + 1 + subj->column_offset + subj->block_offset; e->end_column = end_column + 1 + subj->column_offset + subj->block_offset; return e; } // Create an inline with no value. static CMARK_INLINE cmark_node *make_simple(cmark_mem *mem, cmark_node_type t) { cmark_node *e = (cmark_node *)mem->calloc(1, sizeof(*e)); cmark_strbuf_init(mem, &e->content, 0); e->type = (uint16_t)t; return e; } // Like make_str, but parses entities. static cmark_node *make_str_with_entities(subject *subj, int start_column, int end_column, cmark_chunk *content) { cmark_strbuf unescaped = CMARK_BUF_INIT(subj->mem); if (houdini_unescape_html(&unescaped, content->data, content->len)) { return make_str(subj, start_column, end_column, cmark_chunk_buf_detach(&unescaped)); } else { return make_str(subj, start_column, end_column, *content); } } // Duplicate a chunk by creating a copy of the buffer not by reusing the // buffer like cmark_chunk_dup does. static cmark_chunk chunk_clone(cmark_mem *mem, cmark_chunk *src) { cmark_chunk c; bufsize_t len = src->len; c.len = len; c.data = (unsigned char *)mem->calloc(len + 1, 1); c.alloc = 1; if (len) memcpy(c.data, src->data, len); c.data[len] = '\0'; return c; } static cmark_chunk cmark_clean_autolink(cmark_mem *mem, cmark_chunk *url, int is_email) { cmark_strbuf buf = CMARK_BUF_INIT(mem); cmark_chunk_trim(url); if (url->len == 0) { cmark_chunk result = CMARK_CHUNK_EMPTY; return result; } if (is_email) cmark_strbuf_puts(&buf, "mailto:"); houdini_unescape_html_f(&buf, url->data, url->len); return cmark_chunk_buf_detach(&buf); } static CMARK_INLINE cmark_node *make_autolink(subject *subj, int start_column, int end_column, cmark_chunk url, int is_email) { cmark_node *link = make_simple(subj->mem, CMARK_NODE_LINK); link->as.link.url = cmark_clean_autolink(subj->mem, &url, is_email); link->as.link.title = cmark_chunk_literal(""); link->start_line = link->end_line = subj->line; link->start_column = start_column + 1; link->end_column = end_column + 1; cmark_node_append_child(link, make_str_with_entities(subj, start_column + 1, end_column - 1, &url)); return link; } static void subject_from_buf(cmark_mem *mem, int line_number, int block_offset, subject *e, cmark_chunk *chunk, cmark_map *refmap) { int i; e->mem = mem; e->input = *chunk; e->line = line_number; e->pos = 0; e->block_offset = block_offset; e->column_offset = 0; e->refmap = refmap; e->last_delim = NULL; e->last_bracket = NULL; for (i = 0; i <= MAXBACKTICKS; i++) { e->backticks[i] = 0; } e->scanned_for_backticks = false; } static CMARK_INLINE int isbacktick(int c) { return (c == '`'); } static CMARK_INLINE unsigned char peek_char_n(subject *subj, bufsize_t n) { // NULL bytes should have been stripped out by now. If they're // present, it's a programming error: assert(!(subj->pos + n < subj->input.len && subj->input.data[subj->pos + n] == 0)); return (subj->pos + n < subj->input.len) ? subj->input.data[subj->pos + n] : 0; } static CMARK_INLINE unsigned char peek_char(subject *subj) { return peek_char_n(subj, 0); } static CMARK_INLINE unsigned char peek_at(subject *subj, bufsize_t pos) { return subj->input.data[pos]; } // Return true if there are more characters in the subject. static CMARK_INLINE int is_eof(subject *subj) { return (subj->pos >= subj->input.len); } // Advance the subject. Doesn't check for eof. #define advance(subj) (subj)->pos += 1 static CMARK_INLINE bool skip_spaces(subject *subj) { bool skipped = false; while (peek_char(subj) == ' ' || peek_char(subj) == '\t') { advance(subj); skipped = true; } return skipped; } static CMARK_INLINE bool skip_line_end(subject *subj) { bool seen_line_end_char = false; if (peek_char(subj) == '\r') { advance(subj); seen_line_end_char = true; } if (peek_char(subj) == '\n') { advance(subj); seen_line_end_char = true; } return seen_line_end_char || is_eof(subj); } // Take characters while a predicate holds, and return a string. static CMARK_INLINE cmark_chunk take_while(subject *subj, int (*f)(int)) { unsigned char c; bufsize_t startpos = subj->pos; bufsize_t len = 0; while ((c = peek_char(subj)) && (*f)(c)) { advance(subj); len++; } return cmark_chunk_dup(&subj->input, startpos, len); } // Return the number of newlines in a given span of text in a subject. If // the number is greater than zero, also return the number of characters // between the last newline and the end of the span in `since_newline`. static int count_newlines(subject *subj, bufsize_t from, bufsize_t len, int *since_newline) { int nls = 0; int since_nl = 0; while (len--) { if (subj->input.data[from++] == '\n') { ++nls; since_nl = 0; } else { ++since_nl; } } if (!nls) return 0; *since_newline = since_nl; return nls; } // Adjust `node`'s `end_line`, `end_column`, and `subj`'s `line` and // `column_offset` according to the number of newlines in a just-matched span // of text in `subj`. static void adjust_subj_node_newlines(subject *subj, cmark_node *node, int matchlen, int extra, int options) { if (!(options & CMARK_OPT_SOURCEPOS)) { return; } int since_newline; int newlines = count_newlines(subj, subj->pos - matchlen - extra, matchlen, &since_newline); if (newlines) { subj->line += newlines; node->end_line += newlines; node->end_column = since_newline; subj->column_offset = -subj->pos + since_newline + extra; } } // Try to process a backtick code span that began with a // span of ticks of length openticklength length (already // parsed). Return 0 if you don't find matching closing // backticks, otherwise return the position in the subject // after the closing backticks. static bufsize_t scan_to_closing_backticks(subject *subj, bufsize_t openticklength) { bool found = false; if (openticklength > MAXBACKTICKS) { // we limit backtick string length because of the array subj->backticks: return 0; } if (subj->scanned_for_backticks && subj->backticks[openticklength] <= subj->pos) { // return if we already know there's no closer return 0; } while (!found) { // read non backticks unsigned char c; while ((c = peek_char(subj)) && c != '`') { advance(subj); } if (is_eof(subj)) { break; } bufsize_t numticks = 0; while (peek_char(subj) == '`') { advance(subj); numticks++; } // store position of ender if (numticks <= MAXBACKTICKS) { subj->backticks[numticks] = subj->pos - numticks; } if (numticks == openticklength) { return (subj->pos); } } // got through whole input without finding closer subj->scanned_for_backticks = true; return 0; } // Destructively modify string, converting newlines to // spaces, then removing a single leading + trailing space. static void S_normalize_code(cmark_strbuf *s) { bufsize_t r, w; for (r = 0, w = 0; r < s->size; ++r) { switch (s->ptr[r]) { case '\r': if (s->ptr[r + 1] != '\n') { s->ptr[w++] = ' '; } break; case '\n': s->ptr[w++] = ' '; break; default: s->ptr[w++] = s->ptr[r]; } } // begins and ends with space? if (s->ptr[0] == ' ' && s->ptr[w - 1] == ' ') { cmark_strbuf_drop(s, 1); cmark_strbuf_truncate(s, w - 2); } else { cmark_strbuf_truncate(s, w); } } // Parse backtick code section or raw backticks, return an inline. // Assumes that the subject has a backtick at the current position. static cmark_node *handle_backticks(subject *subj, int options) { cmark_chunk openticks = take_while(subj, isbacktick); bufsize_t startpos = subj->pos; bufsize_t endpos = scan_to_closing_backticks(subj, openticks.len); if (endpos == 0) { // not found subj->pos = startpos; // rewind return make_str(subj, subj->pos, subj->pos, openticks); } else { cmark_strbuf buf = CMARK_BUF_INIT(subj->mem); cmark_strbuf_set(&buf, subj->input.data + startpos, endpos - startpos - openticks.len); S_normalize_code(&buf); cmark_node *node = make_code(subj, startpos, endpos - openticks.len - 1, cmark_chunk_buf_detach(&buf)); adjust_subj_node_newlines(subj, node, endpos - startpos, openticks.len, options); return node; } } // Scan ***, **, or * and return number scanned, or 0. // Advances position. static int scan_delims(subject *subj, unsigned char c, bool *can_open, bool *can_close) { int numdelims = 0; bufsize_t before_char_pos, after_char_pos; int32_t after_char = 0; int32_t before_char = 0; int len; bool left_flanking, right_flanking; if (subj->pos == 0) { before_char = 10; } else { before_char_pos = subj->pos - 1; // walk back to the beginning of the UTF_8 sequence: while ((peek_at(subj, before_char_pos) >> 6 == 2 || SKIP_CHARS[peek_at(subj, before_char_pos)]) && before_char_pos > 0) { before_char_pos -= 1; } len = cmark_utf8proc_iterate(subj->input.data + before_char_pos, subj->pos - before_char_pos, &before_char); if (len == -1 || (before_char < 256 && SKIP_CHARS[(unsigned char) before_char])) { before_char = 10; } } if (c == '\'' || c == '"') { numdelims++; advance(subj); // limit to 1 delim for quotes } else { while (peek_char(subj) == c) { numdelims++; advance(subj); } } if (subj->pos == subj->input.len) { after_char = 10; } else { after_char_pos = subj->pos; while (SKIP_CHARS[peek_at(subj, after_char_pos)] && after_char_pos < subj->input.len) { after_char_pos += 1; } len = cmark_utf8proc_iterate(subj->input.data + after_char_pos, subj->input.len - after_char_pos, &after_char); if (len == -1 || (after_char < 256 && SKIP_CHARS[(unsigned char) after_char])) { after_char = 10; } } left_flanking = numdelims > 0 && !cmark_utf8proc_is_space(after_char) && (!cmark_utf8proc_is_punctuation(after_char) || cmark_utf8proc_is_space(before_char) || cmark_utf8proc_is_punctuation(before_char)); right_flanking = numdelims > 0 && !cmark_utf8proc_is_space(before_char) && (!cmark_utf8proc_is_punctuation(before_char) || cmark_utf8proc_is_space(after_char) || cmark_utf8proc_is_punctuation(after_char)); if (c == '_') { *can_open = left_flanking && (!right_flanking || cmark_utf8proc_is_punctuation(before_char)); *can_close = right_flanking && (!left_flanking || cmark_utf8proc_is_punctuation(after_char)); } else if (c == '\'' || c == '"') { *can_open = left_flanking && !right_flanking && before_char != ']' && before_char != ')'; *can_close = right_flanking; } else { *can_open = left_flanking; *can_close = right_flanking; } return numdelims; } /* static void print_delimiters(subject *subj) { delimiter *delim; delim = subj->last_delim; while (delim != NULL) { printf("Item at stack pos %p: %d %d %d next(%p) prev(%p)\n", (void*)delim, delim->delim_char, delim->can_open, delim->can_close, (void*)delim->next, (void*)delim->previous); delim = delim->previous; } } */ static void remove_delimiter(subject *subj, delimiter *delim) { if (delim == NULL) return; if (delim->next == NULL) { // end of list: assert(delim == subj->last_delim); subj->last_delim = delim->previous; } else { delim->next->previous = delim->previous; } if (delim->previous != NULL) { delim->previous->next = delim->next; } subj->mem->free(delim); } static void pop_bracket(subject *subj) { bracket *b; if (subj->last_bracket == NULL) return; b = subj->last_bracket; subj->last_bracket = subj->last_bracket->previous; subj->mem->free(b); } static void push_delimiter(subject *subj, unsigned char c, bool can_open, bool can_close, cmark_node *inl_text) { delimiter *delim = (delimiter *)subj->mem->calloc(1, sizeof(delimiter)); delim->delim_char = c; delim->can_open = can_open; delim->can_close = can_close; delim->inl_text = inl_text; delim->length = inl_text->as.literal.len; delim->previous = subj->last_delim; delim->next = NULL; if (delim->previous != NULL) { delim->previous->next = delim; } subj->last_delim = delim; } static void push_bracket(subject *subj, bool image, cmark_node *inl_text) { bracket *b = (bracket *)subj->mem->calloc(1, sizeof(bracket)); if (subj->last_bracket != NULL) { subj->last_bracket->bracket_after = true; } b->image = image; b->active = true; b->inl_text = inl_text; b->previous = subj->last_bracket; b->previous_delimiter = subj->last_delim; b->position = subj->pos; b->bracket_after = false; subj->last_bracket = b; } // Assumes the subject has a c at the current position. static cmark_node *handle_delim(subject *subj, unsigned char c, bool smart) { bufsize_t numdelims; cmark_node *inl_text; bool can_open, can_close; cmark_chunk contents; numdelims = scan_delims(subj, c, &can_open, &can_close); if (c == '\'' && smart) { contents = cmark_chunk_literal(RIGHTSINGLEQUOTE); } else if (c == '"' && smart) { contents = cmark_chunk_literal(can_close ? RIGHTDOUBLEQUOTE : LEFTDOUBLEQUOTE); } else { contents = cmark_chunk_dup(&subj->input, subj->pos - numdelims, numdelims); } inl_text = make_str(subj, subj->pos - numdelims, subj->pos - 1, contents); if ((can_open || can_close) && (!(c == '\'' || c == '"') || smart)) { push_delimiter(subj, c, can_open, can_close, inl_text); } return inl_text; } // Assumes we have a hyphen at the current position. static cmark_node *handle_hyphen(subject *subj, bool smart) { int startpos = subj->pos; advance(subj); if (!smart || peek_char(subj) != '-') { return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("-")); } while (smart && peek_char(subj) == '-') { advance(subj); } int numhyphens = subj->pos - startpos; int en_count = 0; int em_count = 0; int i; cmark_strbuf buf = CMARK_BUF_INIT(subj->mem); if (numhyphens % 3 == 0) { // if divisible by 3, use all em dashes em_count = numhyphens / 3; } else if (numhyphens % 2 == 0) { // if divisible by 2, use all en dashes en_count = numhyphens / 2; } else if (numhyphens % 3 == 2) { // use one en dash at end en_count = 1; em_count = (numhyphens - 2) / 3; } else { // use two en dashes at the end en_count = 2; em_count = (numhyphens - 4) / 3; } for (i = em_count; i > 0; i--) { cmark_strbuf_puts(&buf, EMDASH); } for (i = en_count; i > 0; i--) { cmark_strbuf_puts(&buf, ENDASH); } return make_str(subj, startpos, subj->pos - 1, cmark_chunk_buf_detach(&buf)); } // Assumes we have a period at the current position. static cmark_node *handle_period(subject *subj, bool smart) { advance(subj); if (smart && peek_char(subj) == '.') { advance(subj); if (peek_char(subj) == '.') { advance(subj); return make_str(subj, subj->pos - 3, subj->pos - 1, cmark_chunk_literal(ELLIPSES)); } else { return make_str(subj, subj->pos - 2, subj->pos - 1, cmark_chunk_literal("..")); } } else { return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal(".")); } } static cmark_syntax_extension *get_extension_for_special_char(cmark_parser *parser, unsigned char c) { cmark_llist *tmp_ext; for (tmp_ext = parser->inline_syntax_extensions; tmp_ext; tmp_ext=tmp_ext->next) { cmark_syntax_extension *ext = (cmark_syntax_extension *) tmp_ext->data; cmark_llist *tmp_char; for (tmp_char = ext->special_inline_chars; tmp_char; tmp_char=tmp_char->next) { unsigned char tmp_c = (unsigned char)(size_t)tmp_char->data; if (tmp_c == c) { return ext; } } } return NULL; } static void process_emphasis(cmark_parser *parser, subject *subj, delimiter *stack_bottom) { delimiter *closer = subj->last_delim; delimiter *opener; delimiter *old_closer; bool opener_found; bool odd_match; delimiter *openers_bottom[3][128]; int i; // initialize openers_bottom: memset(&openers_bottom, 0, sizeof(openers_bottom)); for (i=0; i < 3; i++) { openers_bottom[i]['*'] = stack_bottom; openers_bottom[i]['_'] = stack_bottom; openers_bottom[i]['\''] = stack_bottom; openers_bottom[i]['"'] = stack_bottom; } // move back to first relevant delim. while (closer != NULL && closer->previous != stack_bottom) { closer = closer->previous; } // now move forward, looking for closers, and handling each while (closer != NULL) { cmark_syntax_extension *extension = get_extension_for_special_char(parser, closer->delim_char); if (closer->can_close) { // Now look backwards for first matching opener: opener = closer->previous; opener_found = false; odd_match = false; while (opener != NULL && opener != stack_bottom && opener != openers_bottom[closer->length % 3][closer->delim_char]) { if (opener->can_open && opener->delim_char == closer->delim_char) { // interior closer of size 2 can't match opener of size 1 // or of size 1 can't match 2 odd_match = (closer->can_open || opener->can_close) && ((opener->length + closer->length) % 3 == 0); if (!odd_match) { opener_found = true; break; } } opener = opener->previous; } old_closer = closer; if (extension) { if (opener_found) closer = extension->insert_inline_from_delim(extension, parser, subj, opener, closer); else closer = closer->next; } else if (closer->delim_char == '*' || closer->delim_char == '_') { if (opener_found) { closer = S_insert_emph(subj, opener, closer); } else { closer = closer->next; } } else if (closer->delim_char == '\'') { cmark_chunk_free(subj->mem, &closer->inl_text->as.literal); closer->inl_text->as.literal = cmark_chunk_literal(RIGHTSINGLEQUOTE); if (opener_found) { cmark_chunk_free(subj->mem, &opener->inl_text->as.literal); opener->inl_text->as.literal = cmark_chunk_literal(LEFTSINGLEQUOTE); } closer = closer->next; } else if (closer->delim_char == '"') { cmark_chunk_free(subj->mem, &closer->inl_text->as.literal); closer->inl_text->as.literal = cmark_chunk_literal(RIGHTDOUBLEQUOTE); if (opener_found) { cmark_chunk_free(subj->mem, &opener->inl_text->as.literal); opener->inl_text->as.literal = cmark_chunk_literal(LEFTDOUBLEQUOTE); } closer = closer->next; } if (!opener_found) { // set lower bound for future searches for openers openers_bottom[old_closer->length % 3][old_closer->delim_char] = old_closer->previous; if (!old_closer->can_open) { // we can remove a closer that can't be an // opener, once we've seen there's no // matching opener: remove_delimiter(subj, old_closer); } } } else { closer = closer->next; } } // free all delimiters in list until stack_bottom: while (subj->last_delim != NULL && subj->last_delim != stack_bottom) { remove_delimiter(subj, subj->last_delim); } } static delimiter *S_insert_emph(subject *subj, delimiter *opener, delimiter *closer) { delimiter *delim, *tmp_delim; bufsize_t use_delims; cmark_node *opener_inl = opener->inl_text; cmark_node *closer_inl = closer->inl_text; bufsize_t opener_num_chars = opener_inl->as.literal.len; bufsize_t closer_num_chars = closer_inl->as.literal.len; cmark_node *tmp, *tmpnext, *emph; // calculate the actual number of characters used from this closer use_delims = (closer_num_chars >= 2 && opener_num_chars >= 2) ? 2 : 1; // remove used characters from associated inlines. opener_num_chars -= use_delims; closer_num_chars -= use_delims; opener_inl->as.literal.len = opener_num_chars; closer_inl->as.literal.len = closer_num_chars; // free delimiters between opener and closer delim = closer->previous; while (delim != NULL && delim != opener) { tmp_delim = delim->previous; remove_delimiter(subj, delim); delim = tmp_delim; } // create new emph or strong, and splice it in to our inlines // between the opener and closer emph = use_delims == 1 ? make_emph(subj->mem) : make_strong(subj->mem); tmp = opener_inl->next; while (tmp && tmp != closer_inl) { tmpnext = tmp->next; cmark_node_append_child(emph, tmp); tmp = tmpnext; } cmark_node_insert_after(opener_inl, emph); emph->start_line = opener_inl->start_line; emph->end_line = closer_inl->end_line; emph->start_column = opener_inl->start_column; emph->end_column = closer_inl->end_column; // if opener has 0 characters, remove it and its associated inline if (opener_num_chars == 0) { cmark_node_free(opener_inl); remove_delimiter(subj, opener); } // if closer has 0 characters, remove it and its associated inline if (closer_num_chars == 0) { // remove empty closer inline cmark_node_free(closer_inl); // remove closer from list tmp_delim = closer->next; remove_delimiter(subj, closer); closer = tmp_delim; } return closer; } // Parse backslash-escape or just a backslash, returning an inline. static cmark_node *handle_backslash(cmark_parser *parser, subject *subj) { advance(subj); unsigned char nextchar = peek_char(subj); if ((parser->backslash_ispunct ? parser->backslash_ispunct : cmark_ispunct)(nextchar)) { // only ascii symbols and newline can be escaped advance(subj); return make_str(subj, subj->pos - 2, subj->pos - 1, cmark_chunk_dup(&subj->input, subj->pos - 1, 1)); } else if (!is_eof(subj) && skip_line_end(subj)) { return make_linebreak(subj->mem); } else { return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("\\")); } } // Parse an entity or a regular "&" string. // Assumes the subject has an '&' character at the current position. static cmark_node *handle_entity(subject *subj) { cmark_strbuf ent = CMARK_BUF_INIT(subj->mem); bufsize_t len; advance(subj); len = houdini_unescape_ent(&ent, subj->input.data + subj->pos, subj->input.len - subj->pos); if (len == 0) return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("&")); subj->pos += len; return make_str(subj, subj->pos - 1 - len, subj->pos - 1, cmark_chunk_buf_detach(&ent)); } // Clean a URL: remove surrounding whitespace, and remove \ that escape // punctuation. cmark_chunk cmark_clean_url(cmark_mem *mem, cmark_chunk *url) { cmark_strbuf buf = CMARK_BUF_INIT(mem); cmark_chunk_trim(url); if (url->len == 0) { cmark_chunk result = CMARK_CHUNK_EMPTY; return result; } houdini_unescape_html_f(&buf, url->data, url->len); cmark_strbuf_unescape(&buf); return cmark_chunk_buf_detach(&buf); } cmark_chunk cmark_clean_title(cmark_mem *mem, cmark_chunk *title) { cmark_strbuf buf = CMARK_BUF_INIT(mem); unsigned char first, last; if (title->len == 0) { cmark_chunk result = CMARK_CHUNK_EMPTY; return result; } first = title->data[0]; last = title->data[title->len - 1]; // remove surrounding quotes if any: if ((first == '\'' && last == '\'') || (first == '(' && last == ')') || (first == '"' && last == '"')) { houdini_unescape_html_f(&buf, title->data + 1, title->len - 2); } else { houdini_unescape_html_f(&buf, title->data, title->len); } cmark_strbuf_unescape(&buf); return cmark_chunk_buf_detach(&buf); } // Parse an autolink or HTML tag. // Assumes the subject has a '<' character at the current position. static cmark_node *handle_pointy_brace(subject *subj, int options) { bufsize_t matchlen = 0; cmark_chunk contents; advance(subj); // advance past first < // first try to match a URL autolink matchlen = scan_autolink_uri(&subj->input, subj->pos); if (matchlen > 0) { contents = cmark_chunk_dup(&subj->input, subj->pos, matchlen - 1); subj->pos += matchlen; return make_autolink(subj, subj->pos - 1 - matchlen, subj->pos - 1, contents, 0); } // next try to match an email autolink matchlen = scan_autolink_email(&subj->input, subj->pos); if (matchlen > 0) { contents = cmark_chunk_dup(&subj->input, subj->pos, matchlen - 1); subj->pos += matchlen; return make_autolink(subj, subj->pos - 1 - matchlen, subj->pos - 1, contents, 1); } // finally, try to match an html tag matchlen = scan_html_tag(&subj->input, subj->pos); if (matchlen > 0) { contents = cmark_chunk_dup(&subj->input, subj->pos - 1, matchlen + 1); subj->pos += matchlen; cmark_node *node = make_raw_html(subj, subj->pos - matchlen - 1, subj->pos - 1, contents); adjust_subj_node_newlines(subj, node, matchlen, 1, options); return node; } if (options & CMARK_OPT_LIBERAL_HTML_TAG) { matchlen = scan_liberal_html_tag(&subj->input, subj->pos); if (matchlen > 0) { contents = cmark_chunk_dup(&subj->input, subj->pos - 1, matchlen + 1); subj->pos += matchlen; cmark_node *node = make_raw_html(subj, subj->pos - matchlen - 1, subj->pos - 1, contents); adjust_subj_node_newlines(subj, node, matchlen, 1, options); return node; } } // if nothing matches, just return the opening <: return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("<")); } // Parse a link label. Returns 1 if successful. // Note: unescaped brackets are not allowed in labels. // The label begins with `[` and ends with the first `]` character // encountered. Backticks in labels do not start code spans. static int link_label(subject *subj, cmark_chunk *raw_label) { bufsize_t startpos = subj->pos; int length = 0; unsigned char c; // advance past [ if (peek_char(subj) == '[') { advance(subj); } else { return 0; } while ((c = peek_char(subj)) && c != '[' && c != ']') { if (c == '\\') { advance(subj); length++; if (cmark_ispunct(peek_char(subj))) { advance(subj); length++; } } else { advance(subj); length++; } if (length > MAX_LINK_LABEL_LENGTH) { goto noMatch; } } if (c == ']') { // match found *raw_label = cmark_chunk_dup(&subj->input, startpos + 1, subj->pos - (startpos + 1)); cmark_chunk_trim(raw_label); advance(subj); // advance past ] return 1; } noMatch: subj->pos = startpos; // rewind return 0; } static bufsize_t manual_scan_link_url_2(cmark_chunk *input, bufsize_t offset, cmark_chunk *output) { bufsize_t i = offset; size_t nb_p = 0; while (i < input->len) { if (input->data[i] == '\\' && i + 1 < input-> len && cmark_ispunct(input->data[i+1])) i += 2; else if (input->data[i] == '(') { ++nb_p; ++i; if (nb_p > 32) return -1; } else if (input->data[i] == ')') { if (nb_p == 0) break; --nb_p; ++i; } else if (cmark_isspace(input->data[i])) break; else ++i; } if (i >= input->len) return -1; { cmark_chunk result = {input->data + offset, i - offset, 0}; *output = result; } return i - offset; } static bufsize_t manual_scan_link_url(cmark_chunk *input, bufsize_t offset, cmark_chunk *output) { bufsize_t i = offset; if (i < input->len && input->data[i] == '<') { ++i; while (i < input->len) { if (input->data[i] == '>') { ++i; break; } else if (input->data[i] == '\\') i += 2; else if (input->data[i] == '\n' || input->data[i] == '<') return manual_scan_link_url_2(input, offset, output); else ++i; } } else { return manual_scan_link_url_2(input, offset, output); } if (i >= input->len) return -1; { cmark_chunk result = {input->data + offset + 1, i - 2 - offset, 0}; *output = result; } return i - offset; } // Return a link, an image, or a literal close bracket. static cmark_node *handle_close_bracket(cmark_parser *parser, subject *subj) { bufsize_t initial_pos, after_link_text_pos; bufsize_t endurl, starttitle, endtitle, endall; bufsize_t sps, n; cmark_reference *ref = NULL; cmark_chunk url_chunk, title_chunk; cmark_chunk url, title; bracket *opener; cmark_node *inl; cmark_chunk raw_label; int found_label; cmark_node *tmp, *tmpnext; bool is_image; advance(subj); // advance past ] initial_pos = subj->pos; // get last [ or ![ opener = subj->last_bracket; if (opener == NULL) { return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("]")); } if (!opener->active) { // take delimiter off stack pop_bracket(subj); return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("]")); } // If we got here, we matched a potential link/image text. // Now we check to see if it's a link/image. is_image = opener->image; after_link_text_pos = subj->pos; // First, look for an inline link. if (peek_char(subj) == '(' && ((sps = scan_spacechars(&subj->input, subj->pos + 1)) > -1) && ((n = manual_scan_link_url(&subj->input, subj->pos + 1 + sps, &url_chunk)) > -1)) { // try to parse an explicit link: endurl = subj->pos + 1 + sps + n; starttitle = endurl + scan_spacechars(&subj->input, endurl); // ensure there are spaces btw url and title endtitle = (starttitle == endurl) ? starttitle : starttitle + scan_link_title(&subj->input, starttitle); endall = endtitle + scan_spacechars(&subj->input, endtitle); if (peek_at(subj, endall) == ')') { subj->pos = endall + 1; title_chunk = cmark_chunk_dup(&subj->input, starttitle, endtitle - starttitle); url = cmark_clean_url(subj->mem, &url_chunk); title = cmark_clean_title(subj->mem, &title_chunk); cmark_chunk_free(subj->mem, &url_chunk); cmark_chunk_free(subj->mem, &title_chunk); goto match; } else { // it could still be a shortcut reference link subj->pos = after_link_text_pos; } } // Next, look for a following [link label] that matches in refmap. // skip spaces raw_label = cmark_chunk_literal(""); found_label = link_label(subj, &raw_label); if (!found_label) { // If we have a shortcut reference link, back up // to before the spacse we skipped. subj->pos = initial_pos; } if ((!found_label || raw_label.len == 0) && !opener->bracket_after) { cmark_chunk_free(subj->mem, &raw_label); raw_label = cmark_chunk_dup(&subj->input, opener->position, initial_pos - opener->position - 1); found_label = true; } if (found_label) { ref = (cmark_reference *)cmark_map_lookup(subj->refmap, &raw_label); cmark_chunk_free(subj->mem, &raw_label); } if (ref != NULL) { // found url = chunk_clone(subj->mem, &ref->url); title = chunk_clone(subj->mem, &ref->title); goto match; } else { goto noMatch; } noMatch: // If we fall through to here, it means we didn't match a link. // What if we're a footnote link? if (parser->options & CMARK_OPT_FOOTNOTES && opener->inl_text->next && opener->inl_text->next->type == CMARK_NODE_TEXT && !opener->inl_text->next->next) { cmark_chunk *literal = &opener->inl_text->next->as.literal; if (literal->len > 1 && literal->data[0] == '^') { inl = make_simple(subj->mem, CMARK_NODE_FOOTNOTE_REFERENCE); inl->as.literal = cmark_chunk_dup(literal, 1, literal->len - 1); inl->start_line = inl->end_line = subj->line; inl->start_column = opener->inl_text->start_column; inl->end_column = subj->pos + subj->column_offset + subj->block_offset; cmark_node_insert_before(opener->inl_text, inl); cmark_node_free(opener->inl_text->next); cmark_node_free(opener->inl_text); process_emphasis(parser, subj, opener->previous_delimiter); pop_bracket(subj); return NULL; } } pop_bracket(subj); // remove this opener from delimiter list subj->pos = initial_pos; return make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("]")); match: inl = make_simple(subj->mem, is_image ? CMARK_NODE_IMAGE : CMARK_NODE_LINK); inl->as.link.url = url; inl->as.link.title = title; inl->start_line = inl->end_line = subj->line; inl->start_column = opener->inl_text->start_column; inl->end_column = subj->pos + subj->column_offset + subj->block_offset; cmark_node_insert_before(opener->inl_text, inl); // Add link text: tmp = opener->inl_text->next; while (tmp) { tmpnext = tmp->next; cmark_node_append_child(inl, tmp); tmp = tmpnext; } // Free the bracket [: cmark_node_free(opener->inl_text); process_emphasis(parser, subj, opener->previous_delimiter); pop_bracket(subj); // Now, if we have a link, we also want to deactivate earlier link // delimiters. (This code can be removed if we decide to allow links // inside links.) if (!is_image) { opener = subj->last_bracket; while (opener != NULL) { if (!opener->image) { if (!opener->active) { break; } else { opener->active = false; } } opener = opener->previous; } } return NULL; } // Parse a hard or soft linebreak, returning an inline. // Assumes the subject has a cr or newline at the current position. static cmark_node *handle_newline(subject *subj) { bufsize_t nlpos = subj->pos; // skip over cr, crlf, or lf: if (peek_at(subj, subj->pos) == '\r') { advance(subj); } if (peek_at(subj, subj->pos) == '\n') { advance(subj); } ++subj->line; subj->column_offset = -subj->pos; // skip spaces at beginning of line skip_spaces(subj); if (nlpos > 1 && peek_at(subj, nlpos - 1) == ' ' && peek_at(subj, nlpos - 2) == ' ') { return make_linebreak(subj->mem); } else { return make_softbreak(subj->mem); } } // "\r\n\\`&_*[]pos + 1; while (n < subj->input.len) { if (SPECIAL_CHARS[subj->input.data[n]]) return n; if (options & CMARK_OPT_SMART && SMART_PUNCT_CHARS[subj->input.data[n]]) return n; n++; } return subj->input.len; } void cmark_inlines_add_special_character(unsigned char c, bool emphasis) { SPECIAL_CHARS[c] = 1; if (emphasis) SKIP_CHARS[c] = 1; } void cmark_inlines_remove_special_character(unsigned char c, bool emphasis) { SPECIAL_CHARS[c] = 0; if (emphasis) SKIP_CHARS[c] = 0; } static cmark_node *try_extensions(cmark_parser *parser, cmark_node *parent, unsigned char c, subject *subj) { cmark_node *res = NULL; cmark_llist *tmp; for (tmp = parser->inline_syntax_extensions; tmp; tmp = tmp->next) { cmark_syntax_extension *ext = (cmark_syntax_extension *) tmp->data; res = ext->match_inline(ext, parser, parent, c, subj); if (res) break; } return res; } // Parse an inline, advancing subject, and add it as a child of parent. // Return 0 if no inline can be parsed, 1 otherwise. static int parse_inline(cmark_parser *parser, subject *subj, cmark_node *parent, int options) { cmark_node *new_inl = NULL; cmark_chunk contents; unsigned char c; bufsize_t startpos, endpos; c = peek_char(subj); if (c == 0) { return 0; } switch (c) { case '\r': case '\n': new_inl = handle_newline(subj); break; case '`': new_inl = handle_backticks(subj, options); break; case '\\': new_inl = handle_backslash(parser, subj); break; case '&': new_inl = handle_entity(subj); break; case '<': new_inl = handle_pointy_brace(subj, options); break; case '*': case '_': case '\'': case '"': new_inl = handle_delim(subj, c, (options & CMARK_OPT_SMART) != 0); break; case '-': new_inl = handle_hyphen(subj, (options & CMARK_OPT_SMART) != 0); break; case '.': new_inl = handle_period(subj, (options & CMARK_OPT_SMART) != 0); break; case '[': advance(subj); new_inl = make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("[")); push_bracket(subj, false, new_inl); break; case ']': new_inl = handle_close_bracket(parser, subj); break; case '!': advance(subj); if (peek_char(subj) == '[' && peek_char_n(subj, 1) != '^') { advance(subj); new_inl = make_str(subj, subj->pos - 2, subj->pos - 1, cmark_chunk_literal("![")); push_bracket(subj, true, new_inl); } else { new_inl = make_str(subj, subj->pos - 1, subj->pos - 1, cmark_chunk_literal("!")); } break; default: new_inl = try_extensions(parser, parent, c, subj); if (new_inl != NULL) break; endpos = subject_find_special_char(subj, options); contents = cmark_chunk_dup(&subj->input, subj->pos, endpos - subj->pos); startpos = subj->pos; subj->pos = endpos; // if we're at a newline, strip trailing spaces. if (S_is_line_end_char(peek_char(subj))) { cmark_chunk_rtrim(&contents); } new_inl = make_str(subj, startpos, endpos - 1, contents); } if (new_inl != NULL) { cmark_node_append_child(parent, new_inl); } return 1; } // Parse inlines from parent's string_content, adding as children of parent. void cmark_parse_inlines(cmark_parser *parser, cmark_node *parent, cmark_map *refmap, int options) { subject subj; cmark_chunk content = {parent->content.ptr, parent->content.size, 0}; subject_from_buf(parser->mem, parent->start_line, parent->start_column - 1 + parent->internal_offset, &subj, &content, refmap); cmark_chunk_rtrim(&subj.input); while (!is_eof(&subj) && parse_inline(parser, &subj, parent, options)) ; process_emphasis(parser, &subj, NULL); // free bracket and delim stack while (subj.last_delim) { remove_delimiter(&subj, subj.last_delim); } while (subj.last_bracket) { pop_bracket(&subj); } } // Parse zero or more space characters, including at most one newline. static void spnl(subject *subj) { skip_spaces(subj); if (skip_line_end(subj)) { skip_spaces(subj); } } // Parse reference. Assumes string begins with '[' character. // Modify refmap if a reference is encountered. // Return 0 if no reference found, otherwise position of subject // after reference is parsed. bufsize_t cmark_parse_reference_inline(cmark_mem *mem, cmark_chunk *input, cmark_map *refmap) { subject subj; cmark_chunk lab; cmark_chunk url; cmark_chunk title; bufsize_t matchlen = 0; bufsize_t beforetitle; subject_from_buf(mem, -1, 0, &subj, input, NULL); // parse label: if (!link_label(&subj, &lab) || lab.len == 0) return 0; // colon: if (peek_char(&subj) == ':') { advance(&subj); } else { return 0; } // parse link url: spnl(&subj); if ((matchlen = manual_scan_link_url(&subj.input, subj.pos, &url)) > -1 && url.len > 0) { subj.pos += matchlen; } else { return 0; } // parse optional link_title beforetitle = subj.pos; spnl(&subj); matchlen = subj.pos == beforetitle ? 0 : scan_link_title(&subj.input, subj.pos); if (matchlen) { title = cmark_chunk_dup(&subj.input, subj.pos, matchlen); subj.pos += matchlen; } else { subj.pos = beforetitle; title = cmark_chunk_literal(""); } // parse final spaces and newline: skip_spaces(&subj); if (!skip_line_end(&subj)) { if (matchlen) { // try rewinding before title subj.pos = beforetitle; skip_spaces(&subj); if (!skip_line_end(&subj)) { return 0; } } else { return 0; } } // insert reference into refmap cmark_reference_create(refmap, &lab, &url, &title); return subj.pos; } unsigned char cmark_inline_parser_peek_char(cmark_inline_parser *parser) { return peek_char(parser); } unsigned char cmark_inline_parser_peek_at(cmark_inline_parser *parser, bufsize_t pos) { return peek_at(parser, pos); } int cmark_inline_parser_is_eof(cmark_inline_parser *parser) { return is_eof(parser); } static char * my_strndup (const char *s, size_t n) { char *result; size_t len = strlen (s); if (n < len) len = n; result = (char *) malloc (len + 1); if (!result) return 0; result[len] = '\0'; return (char *) memcpy (result, s, len); } char *cmark_inline_parser_take_while(cmark_inline_parser *parser, cmark_inline_predicate pred) { unsigned char c; bufsize_t startpos = parser->pos; bufsize_t len = 0; while ((c = peek_char(parser)) && (*pred)(c)) { advance(parser); len++; } return my_strndup((const char *) parser->input.data + startpos, len); } void cmark_inline_parser_push_delimiter(cmark_inline_parser *parser, unsigned char c, int can_open, int can_close, cmark_node *inl_text) { push_delimiter(parser, c, can_open != 0, can_close != 0, inl_text); } void cmark_inline_parser_remove_delimiter(cmark_inline_parser *parser, delimiter *delim) { remove_delimiter(parser, delim); } int cmark_inline_parser_scan_delimiters(cmark_inline_parser *parser, int max_delims, unsigned char c, int *left_flanking, int *right_flanking, int *punct_before, int *punct_after) { int numdelims = 0; bufsize_t before_char_pos; int32_t after_char = 0; int32_t before_char = 0; int len; bool space_before, space_after; if (parser->pos == 0) { before_char = 10; } else { before_char_pos = parser->pos - 1; // walk back to the beginning of the UTF_8 sequence: while (peek_at(parser, before_char_pos) >> 6 == 2 && before_char_pos > 0) { before_char_pos -= 1; } len = cmark_utf8proc_iterate(parser->input.data + before_char_pos, parser->pos - before_char_pos, &before_char); if (len == -1) { before_char = 10; } } while (peek_char(parser) == c && numdelims < max_delims) { numdelims++; advance(parser); } len = cmark_utf8proc_iterate(parser->input.data + parser->pos, parser->input.len - parser->pos, &after_char); if (len == -1) { after_char = 10; } *punct_before = cmark_utf8proc_is_punctuation(before_char); *punct_after = cmark_utf8proc_is_punctuation(after_char); space_before = cmark_utf8proc_is_space(before_char) != 0; space_after = cmark_utf8proc_is_space(after_char) != 0; *left_flanking = numdelims > 0 && !cmark_utf8proc_is_space(after_char) && !(*punct_after && !space_before && !*punct_before); *right_flanking = numdelims > 0 && !cmark_utf8proc_is_space(before_char) && !(*punct_before && !space_after && !*punct_after); return numdelims; } void cmark_inline_parser_advance_offset(cmark_inline_parser *parser) { advance(parser); } int cmark_inline_parser_get_offset(cmark_inline_parser *parser) { return parser->pos; } void cmark_inline_parser_set_offset(cmark_inline_parser *parser, int offset) { parser->pos = offset; } int cmark_inline_parser_get_column(cmark_inline_parser *parser) { return parser->pos + 1 + parser->column_offset + parser->block_offset; } cmark_chunk *cmark_inline_parser_get_chunk(cmark_inline_parser *parser) { return &parser->input; } int cmark_inline_parser_in_bracket(cmark_inline_parser *parser, int image) { for (bracket *b = parser->last_bracket; b; b = b->previous) if (b->active && b->image == (image != 0)) return 1; return 0; } void cmark_node_unput(cmark_node *node, int n) { node = node->last_child; while (n > 0 && node && node->type == CMARK_NODE_TEXT) { if (node->as.literal.len < n) { n -= node->as.literal.len; node->as.literal.len = 0; } else { node->as.literal.len -= n; n = 0; } node = node->prev; } } delimiter *cmark_inline_parser_get_last_delimiter(cmark_inline_parser *parser) { return parser->last_delim; } int cmark_inline_parser_get_line(cmark_inline_parser *parser) { return parser->line; } cmark-gfm-0.1.8/cbits/blocks.c0000644000000000000000000013473013442034251014305 0ustar0000000000000000/** * Block parsing implementation. * * For a high-level overview of the block parsing process, * see http://spec.commonmark.org/0.24/#phase-1-block-structure */ #include #include #include #include "cmark_ctype.h" #include "syntax_extension.h" #include "config.h" #include "parser.h" #include "cmark-gfm.h" #include "node.h" #include "references.h" #include "utf8.h" #include "scanners.h" #include "inlines.h" #include "houdini.h" #include "buffer.h" #include "footnotes.h" #define CODE_INDENT 4 #define TAB_STOP 4 #ifndef MIN #define MIN(x, y) ((x < y) ? x : y) #endif #define peek_at(i, n) (i)->data[n] static bool S_last_line_blank(const cmark_node *node) { return (node->flags & CMARK_NODE__LAST_LINE_BLANK) != 0; } static CMARK_INLINE cmark_node_type S_type(const cmark_node *node) { return (cmark_node_type)node->type; } static void S_set_last_line_blank(cmark_node *node, bool is_blank) { if (is_blank) node->flags |= CMARK_NODE__LAST_LINE_BLANK; else node->flags &= ~CMARK_NODE__LAST_LINE_BLANK; } static CMARK_INLINE bool S_is_line_end_char(char c) { return (c == '\n' || c == '\r'); } static CMARK_INLINE bool S_is_space_or_tab(char c) { return (c == ' ' || c == '\t'); } static void S_parser_feed(cmark_parser *parser, const unsigned char *buffer, size_t len, bool eof); static void S_process_line(cmark_parser *parser, const unsigned char *buffer, bufsize_t bytes); static cmark_node *make_block(cmark_mem *mem, cmark_node_type tag, int start_line, int start_column) { cmark_node *e; e = (cmark_node *)mem->calloc(1, sizeof(*e)); cmark_strbuf_init(mem, &e->content, 32); e->type = (uint16_t)tag; e->flags = CMARK_NODE__OPEN; e->start_line = start_line; e->start_column = start_column; e->end_line = start_line; return e; } // Create a root document node. static cmark_node *make_document(cmark_mem *mem) { cmark_node *e = make_block(mem, CMARK_NODE_DOCUMENT, 1, 1); return e; } int cmark_parser_attach_syntax_extension(cmark_parser *parser, cmark_syntax_extension *extension) { parser->syntax_extensions = cmark_llist_append(parser->mem, parser->syntax_extensions, extension); if (extension->match_inline || extension->insert_inline_from_delim) { parser->inline_syntax_extensions = cmark_llist_append( parser->mem, parser->inline_syntax_extensions, extension); } return 1; } static void cmark_parser_dispose(cmark_parser *parser) { if (parser->root) cmark_node_free(parser->root); if (parser->refmap) cmark_map_free(parser->refmap); } static void cmark_parser_reset(cmark_parser *parser) { cmark_llist *saved_exts = parser->syntax_extensions; cmark_llist *saved_inline_exts = parser->inline_syntax_extensions; int saved_options = parser->options; cmark_mem *saved_mem = parser->mem; cmark_parser_dispose(parser); memset(parser, 0, sizeof(cmark_parser)); parser->mem = saved_mem; cmark_strbuf_init(parser->mem, &parser->curline, 256); cmark_strbuf_init(parser->mem, &parser->linebuf, 0); cmark_node *document = make_document(parser->mem); parser->refmap = cmark_reference_map_new(parser->mem); parser->root = document; parser->current = document; parser->last_buffer_ended_with_cr = false; parser->syntax_extensions = saved_exts; parser->inline_syntax_extensions = saved_inline_exts; parser->options = saved_options; } cmark_parser *cmark_parser_new_with_mem(int options, cmark_mem *mem) { cmark_parser *parser = (cmark_parser *)mem->calloc(1, sizeof(cmark_parser)); parser->mem = mem; parser->options = options; cmark_parser_reset(parser); return parser; } cmark_parser *cmark_parser_new(int options) { extern cmark_mem CMARK_DEFAULT_MEM_ALLOCATOR; return cmark_parser_new_with_mem(options, &CMARK_DEFAULT_MEM_ALLOCATOR); } void cmark_parser_free(cmark_parser *parser) { cmark_mem *mem = parser->mem; cmark_parser_dispose(parser); cmark_strbuf_free(&parser->curline); cmark_strbuf_free(&parser->linebuf); cmark_llist_free(parser->mem, parser->syntax_extensions); cmark_llist_free(parser->mem, parser->inline_syntax_extensions); mem->free(parser); } static cmark_node *finalize(cmark_parser *parser, cmark_node *b); // Returns true if line has only space characters, else false. static bool is_blank(cmark_strbuf *s, bufsize_t offset) { while (offset < s->size) { switch (s->ptr[offset]) { case '\r': case '\n': return true; case ' ': offset++; break; case '\t': offset++; break; default: return false; } } return true; } static CMARK_INLINE bool accepts_lines(cmark_node_type block_type) { return (block_type == CMARK_NODE_PARAGRAPH || block_type == CMARK_NODE_HEADING || block_type == CMARK_NODE_CODE_BLOCK); } static CMARK_INLINE bool contains_inlines(cmark_node *node) { if (node->extension && node->extension->contains_inlines_func) { return node->extension->contains_inlines_func(node->extension, node) != 0; } return (node->type == CMARK_NODE_PARAGRAPH || node->type == CMARK_NODE_HEADING); } static void add_line(cmark_node *node, cmark_chunk *ch, cmark_parser *parser) { int chars_to_tab; int i; assert(node->flags & CMARK_NODE__OPEN); if (parser->partially_consumed_tab) { parser->offset += 1; // skip over tab // add space characters: chars_to_tab = TAB_STOP - (parser->column % TAB_STOP); for (i = 0; i < chars_to_tab; i++) { cmark_strbuf_putc(&node->content, ' '); } } cmark_strbuf_put(&node->content, ch->data + parser->offset, ch->len - parser->offset); } static void remove_trailing_blank_lines(cmark_strbuf *ln) { bufsize_t i; unsigned char c; for (i = ln->size - 1; i >= 0; --i) { c = ln->ptr[i]; if (c != ' ' && c != '\t' && !S_is_line_end_char(c)) break; } if (i < 0) { cmark_strbuf_clear(ln); return; } for (; i < ln->size; ++i) { c = ln->ptr[i]; if (!S_is_line_end_char(c)) continue; cmark_strbuf_truncate(ln, i); break; } } // Check to see if a node ends with a blank line, descending // if needed into lists and sublists. static bool ends_with_blank_line(cmark_node *node) { cmark_node *cur = node; while (cur != NULL) { if (S_last_line_blank(cur)) { return true; } if (S_type(cur) == CMARK_NODE_LIST || S_type(cur) == CMARK_NODE_ITEM) { cur = cur->last_child; } else { cur = NULL; } } return false; } static cmark_node *finalize(cmark_parser *parser, cmark_node *b) { bufsize_t pos; cmark_node *item; cmark_node *subitem; cmark_node *parent; parent = b->parent; assert(b->flags & CMARK_NODE__OPEN); // shouldn't call finalize on closed blocks b->flags &= ~CMARK_NODE__OPEN; if (parser->curline.size == 0) { // end of input - line number has not been incremented b->end_line = parser->line_number; b->end_column = parser->last_line_length; } else if (S_type(b) == CMARK_NODE_DOCUMENT || (S_type(b) == CMARK_NODE_CODE_BLOCK && b->as.code.fenced) || (S_type(b) == CMARK_NODE_HEADING && b->as.heading.setext)) { b->end_line = parser->line_number; b->end_column = parser->curline.size; if (b->end_column && parser->curline.ptr[b->end_column - 1] == '\n') b->end_column -= 1; if (b->end_column && parser->curline.ptr[b->end_column - 1] == '\r') b->end_column -= 1; } else { b->end_line = parser->line_number - 1; b->end_column = parser->last_line_length; } cmark_strbuf *node_content = &b->content; switch (S_type(b)) { case CMARK_NODE_PARAGRAPH: { cmark_chunk chunk = {node_content->ptr, node_content->size, 0}; while (chunk.len && chunk.data[0] == '[' && (pos = cmark_parse_reference_inline(parser->mem, &chunk, parser->refmap))) { chunk.data += pos; chunk.len -= pos; } cmark_strbuf_drop(node_content, (node_content->size - chunk.len)); if (is_blank(node_content, 0)) { // remove blank node (former reference def) cmark_node_free(b); } break; } case CMARK_NODE_CODE_BLOCK: if (!b->as.code.fenced) { // indented code remove_trailing_blank_lines(node_content); cmark_strbuf_putc(node_content, '\n'); } else { // first line of contents becomes info for (pos = 0; pos < node_content->size; ++pos) { if (S_is_line_end_char(node_content->ptr[pos])) break; } assert(pos < node_content->size); cmark_strbuf tmp = CMARK_BUF_INIT(parser->mem); houdini_unescape_html_f(&tmp, node_content->ptr, pos); cmark_strbuf_trim(&tmp); cmark_strbuf_unescape(&tmp); b->as.code.info = cmark_chunk_buf_detach(&tmp); if (node_content->ptr[pos] == '\r') pos += 1; if (node_content->ptr[pos] == '\n') pos += 1; cmark_strbuf_drop(node_content, pos); } b->as.code.literal = cmark_chunk_buf_detach(node_content); break; case CMARK_NODE_HTML_BLOCK: b->as.literal = cmark_chunk_buf_detach(node_content); break; case CMARK_NODE_LIST: // determine tight/loose status b->as.list.tight = true; // tight by default item = b->first_child; while (item) { // check for non-final non-empty list item ending with blank line: if (S_last_line_blank(item) && item->next) { b->as.list.tight = false; break; } // recurse into children of list item, to see if there are // spaces between them: subitem = item->first_child; while (subitem) { if (ends_with_blank_line(subitem) && (item->next || subitem->next)) { b->as.list.tight = false; break; } subitem = subitem->next; } if (!(b->as.list.tight)) { break; } item = item->next; } break; default: break; } return parent; } // Add a node as child of another. Return pointer to child. static cmark_node *add_child(cmark_parser *parser, cmark_node *parent, cmark_node_type block_type, int start_column) { assert(parent); // if 'parent' isn't the kind of node that can accept this child, // then back up til we hit a node that can. while (!cmark_node_can_contain_type(parent, block_type)) { parent = finalize(parser, parent); } cmark_node *child = make_block(parser->mem, block_type, parser->line_number, start_column); child->parent = parent; if (parent->last_child) { parent->last_child->next = child; child->prev = parent->last_child; } else { parent->first_child = child; child->prev = NULL; } parent->last_child = child; return child; } void cmark_manage_extensions_special_characters(cmark_parser *parser, int add) { cmark_llist *tmp_ext; for (tmp_ext = parser->inline_syntax_extensions; tmp_ext; tmp_ext=tmp_ext->next) { cmark_syntax_extension *ext = (cmark_syntax_extension *) tmp_ext->data; cmark_llist *tmp_char; for (tmp_char = ext->special_inline_chars; tmp_char; tmp_char=tmp_char->next) { unsigned char c = (unsigned char)(size_t)tmp_char->data; if (add) cmark_inlines_add_special_character(c, ext->emphasis); else cmark_inlines_remove_special_character(c, ext->emphasis); } } } // Walk through node and all children, recursively, parsing // string content into inline content where appropriate. static void process_inlines(cmark_parser *parser, cmark_map *refmap, int options) { cmark_iter *iter = cmark_iter_new(parser->root); cmark_node *cur; cmark_event_type ev_type; cmark_manage_extensions_special_characters(parser, true); while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); if (ev_type == CMARK_EVENT_ENTER) { if (contains_inlines(cur)) { cmark_parse_inlines(parser, cur, refmap, options); } } } cmark_manage_extensions_special_characters(parser, false); cmark_iter_free(iter); } static int sort_footnote_by_ix(const void *_a, const void *_b) { cmark_footnote *a = *(cmark_footnote **)_a; cmark_footnote *b = *(cmark_footnote **)_b; return (int)a->ix - (int)b->ix; } static void process_footnotes(cmark_parser *parser) { // * Collect definitions in a map. // * Iterate the references in the document in order, assigning indices to // definitions in the order they're seen. // * Write out the footnotes at the bottom of the document in index order. cmark_map *map = cmark_footnote_map_new(parser->mem); cmark_iter *iter = cmark_iter_new(parser->root); cmark_node *cur; cmark_event_type ev_type; while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); if (ev_type == CMARK_EVENT_EXIT && cur->type == CMARK_NODE_FOOTNOTE_DEFINITION) { cmark_node_unlink(cur); cmark_footnote_create(map, cur); } } cmark_iter_free(iter); iter = cmark_iter_new(parser->root); unsigned int ix = 0; while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); if (ev_type == CMARK_EVENT_EXIT && cur->type == CMARK_NODE_FOOTNOTE_REFERENCE) { cmark_footnote *footnote = (cmark_footnote *)cmark_map_lookup(map, &cur->as.literal); if (footnote) { if (!footnote->ix) footnote->ix = ++ix; char n[32]; snprintf(n, sizeof(n), "%d", footnote->ix); cmark_chunk_free(parser->mem, &cur->as.literal); cmark_strbuf buf = CMARK_BUF_INIT(parser->mem); cmark_strbuf_puts(&buf, n); cur->as.literal = cmark_chunk_buf_detach(&buf); } else { cmark_node *text = (cmark_node *)parser->mem->calloc(1, sizeof(*text)); cmark_strbuf_init(parser->mem, &text->content, 0); text->type = (uint16_t) CMARK_NODE_TEXT; cmark_strbuf buf = CMARK_BUF_INIT(parser->mem); cmark_strbuf_puts(&buf, "[^"); cmark_strbuf_put(&buf, cur->as.literal.data, cur->as.literal.len); cmark_strbuf_putc(&buf, ']'); text->as.literal = cmark_chunk_buf_detach(&buf); cmark_node_insert_after(cur, text); cmark_node_free(cur); } } } cmark_iter_free(iter); if (map->sorted) { qsort(map->sorted, map->size, sizeof(cmark_map_entry *), sort_footnote_by_ix); for (unsigned int i = 0; i < map->size; ++i) { cmark_footnote *footnote = (cmark_footnote *)map->sorted[i]; if (!footnote->ix) continue; cmark_node_append_child(parser->root, footnote->node); footnote->node = NULL; } } cmark_map_free(map); } // Attempts to parse a list item marker (bullet or enumerated). // On success, returns length of the marker, and populates // data with the details. On failure, returns 0. static bufsize_t parse_list_marker(cmark_mem *mem, cmark_chunk *input, bufsize_t pos, bool interrupts_paragraph, cmark_list **dataptr) { unsigned char c; bufsize_t startpos; cmark_list *data; bufsize_t i; startpos = pos; c = peek_at(input, pos); if (c == '*' || c == '-' || c == '+') { pos++; if (!cmark_isspace(peek_at(input, pos))) { return 0; } if (interrupts_paragraph) { i = pos; // require non-blank content after list marker: while (S_is_space_or_tab(peek_at(input, i))) { i++; } if (peek_at(input, i) == '\n') { return 0; } } data = (cmark_list *)mem->calloc(1, sizeof(*data)); data->marker_offset = 0; // will be adjusted later data->list_type = CMARK_BULLET_LIST; data->bullet_char = c; data->start = 0; data->delimiter = CMARK_NO_DELIM; data->tight = false; } else if (cmark_isdigit(c)) { int start = 0; int digits = 0; do { start = (10 * start) + (peek_at(input, pos) - '0'); pos++; digits++; // We limit to 9 digits to avoid overflow, // assuming max int is 2^31 - 1 // This also seems to be the limit for 'start' in some browsers. } while (digits < 9 && cmark_isdigit(peek_at(input, pos))); if (interrupts_paragraph && start != 1) { return 0; } c = peek_at(input, pos); if (c == '.' || c == ')') { pos++; if (!cmark_isspace(peek_at(input, pos))) { return 0; } if (interrupts_paragraph) { // require non-blank content after list marker: i = pos; while (S_is_space_or_tab(peek_at(input, i))) { i++; } if (S_is_line_end_char(peek_at(input, i))) { return 0; } } data = (cmark_list *)mem->calloc(1, sizeof(*data)); data->marker_offset = 0; // will be adjusted later data->list_type = CMARK_ORDERED_LIST; data->bullet_char = 0; data->start = start; data->delimiter = (c == '.' ? CMARK_PERIOD_DELIM : CMARK_PAREN_DELIM); data->tight = false; } else { return 0; } } else { return 0; } *dataptr = data; return (pos - startpos); } // Return 1 if list item belongs in list, else 0. static int lists_match(cmark_list *list_data, cmark_list *item_data) { return (list_data->list_type == item_data->list_type && list_data->delimiter == item_data->delimiter && // list_data->marker_offset == item_data.marker_offset && list_data->bullet_char == item_data->bullet_char); } static cmark_node *finalize_document(cmark_parser *parser) { while (parser->current != parser->root) { parser->current = finalize(parser, parser->current); } finalize(parser, parser->root); process_inlines(parser, parser->refmap, parser->options); if (parser->options & CMARK_OPT_FOOTNOTES) process_footnotes(parser); return parser->root; } cmark_node *cmark_parse_file(FILE *f, int options) { unsigned char buffer[4096]; cmark_parser *parser = cmark_parser_new(options); size_t bytes; cmark_node *document; while ((bytes = fread(buffer, 1, sizeof(buffer), f)) > 0) { bool eof = bytes < sizeof(buffer); S_parser_feed(parser, buffer, bytes, eof); if (eof) { break; } } document = cmark_parser_finish(parser); cmark_parser_free(parser); return document; } cmark_node *cmark_parse_document(const char *buffer, size_t len, int options) { cmark_parser *parser = cmark_parser_new(options); cmark_node *document; S_parser_feed(parser, (const unsigned char *)buffer, len, true); document = cmark_parser_finish(parser); cmark_parser_free(parser); return document; } void cmark_parser_feed(cmark_parser *parser, const char *buffer, size_t len) { S_parser_feed(parser, (const unsigned char *)buffer, len, false); } void cmark_parser_feed_reentrant(cmark_parser *parser, const char *buffer, size_t len) { cmark_strbuf saved_linebuf; cmark_strbuf_init(parser->mem, &saved_linebuf, 0); cmark_strbuf_puts(&saved_linebuf, cmark_strbuf_cstr(&parser->linebuf)); cmark_strbuf_clear(&parser->linebuf); S_parser_feed(parser, (const unsigned char *)buffer, len, true); cmark_strbuf_sets(&parser->linebuf, cmark_strbuf_cstr(&saved_linebuf)); cmark_strbuf_free(&saved_linebuf); } static void S_parser_feed(cmark_parser *parser, const unsigned char *buffer, size_t len, bool eof) { const unsigned char *end = buffer + len; static const uint8_t repl[] = {239, 191, 189}; if (parser->last_buffer_ended_with_cr && *buffer == '\n') { // skip NL if last buffer ended with CR ; see #117 buffer++; } parser->last_buffer_ended_with_cr = false; while (buffer < end) { const unsigned char *eol; bufsize_t chunk_len; bool process = false; for (eol = buffer; eol < end; ++eol) { if (S_is_line_end_char(*eol)) { process = true; break; } if (*eol == '\0' && eol < end) { break; } } if (eol >= end && eof) { process = true; } chunk_len = (bufsize_t)(eol - buffer); if (process) { if (parser->linebuf.size > 0) { cmark_strbuf_put(&parser->linebuf, buffer, chunk_len); S_process_line(parser, parser->linebuf.ptr, parser->linebuf.size); cmark_strbuf_clear(&parser->linebuf); } else { S_process_line(parser, buffer, chunk_len); } } else { if (eol < end && *eol == '\0') { // omit NULL byte cmark_strbuf_put(&parser->linebuf, buffer, chunk_len); // add replacement character cmark_strbuf_put(&parser->linebuf, repl, 3); } else { cmark_strbuf_put(&parser->linebuf, buffer, chunk_len); } } buffer += chunk_len; if (buffer < end) { if (*buffer == '\0') { // skip over NULL buffer++; } else { // skip over line ending characters if (*buffer == '\r') { buffer++; if (buffer == end) parser->last_buffer_ended_with_cr = true; } if (buffer < end && *buffer == '\n') buffer++; } } } } static void chop_trailing_hashtags(cmark_chunk *ch) { bufsize_t n, orig_n; cmark_chunk_rtrim(ch); orig_n = n = ch->len - 1; // if string ends in space followed by #s, remove these: while (n >= 0 && peek_at(ch, n) == '#') n--; // Check for a space before the final #s: if (n != orig_n && n >= 0 && S_is_space_or_tab(peek_at(ch, n))) { ch->len = n; cmark_chunk_rtrim(ch); } } // Find first nonspace character from current offset, setting // parser->first_nonspace, parser->first_nonspace_column, // parser->indent, and parser->blank. Does not advance parser->offset. static void S_find_first_nonspace(cmark_parser *parser, cmark_chunk *input) { char c; int chars_to_tab = TAB_STOP - (parser->column % TAB_STOP); if (parser->first_nonspace <= parser->offset) { parser->first_nonspace = parser->offset; parser->first_nonspace_column = parser->column; while ((c = peek_at(input, parser->first_nonspace))) { if (c == ' ') { parser->first_nonspace += 1; parser->first_nonspace_column += 1; chars_to_tab = chars_to_tab - 1; if (chars_to_tab == 0) { chars_to_tab = TAB_STOP; } } else if (c == '\t') { parser->first_nonspace += 1; parser->first_nonspace_column += chars_to_tab; chars_to_tab = TAB_STOP; } else { break; } } } parser->indent = parser->first_nonspace_column - parser->column; parser->blank = S_is_line_end_char(peek_at(input, parser->first_nonspace)); } // Advance parser->offset and parser->column. parser->offset is the // byte position in input; parser->column is a virtual column number // that takes into account tabs. (Multibyte characters are not taken // into account, because the Markdown line prefixes we are interested in // analyzing are entirely ASCII.) The count parameter indicates // how far to advance the offset. If columns is true, then count // indicates a number of columns; otherwise, a number of bytes. // If advancing a certain number of columns partially consumes // a tab character, parser->partially_consumed_tab is set to true. static void S_advance_offset(cmark_parser *parser, cmark_chunk *input, bufsize_t count, bool columns) { char c; int chars_to_tab; int chars_to_advance; while (count > 0 && (c = peek_at(input, parser->offset))) { if (c == '\t') { chars_to_tab = TAB_STOP - (parser->column % TAB_STOP); if (columns) { parser->partially_consumed_tab = chars_to_tab > count; chars_to_advance = MIN(count, chars_to_tab); parser->column += chars_to_advance; parser->offset += (parser->partially_consumed_tab ? 0 : 1); count -= chars_to_advance; } else { parser->partially_consumed_tab = false; parser->column += chars_to_tab; parser->offset += 1; count -= 1; } } else { parser->partially_consumed_tab = false; parser->offset += 1; parser->column += 1; // assume ascii; block starts are ascii count -= 1; } } } static bool S_last_child_is_open(cmark_node *container) { return container->last_child && (container->last_child->flags & CMARK_NODE__OPEN); } static bool parse_block_quote_prefix(cmark_parser *parser, cmark_chunk *input) { bool res = false; bufsize_t matched = 0; matched = parser->indent <= 3 && peek_at(input, parser->first_nonspace) == '>'; if (matched) { S_advance_offset(parser, input, parser->indent + 1, true); if (S_is_space_or_tab(peek_at(input, parser->offset))) { S_advance_offset(parser, input, 1, true); } res = true; } return res; } static bool parse_footnote_definition_block_prefix(cmark_parser *parser, cmark_chunk *input, cmark_node *container) { if (parser->indent >= 4) { S_advance_offset(parser, input, 4, true); return true; } else if (input->len > 0 && (input->data[0] == '\n' || (input->data[0] == '\r' && input->data[1] == '\n'))) { return true; } return false; } static bool parse_node_item_prefix(cmark_parser *parser, cmark_chunk *input, cmark_node *container) { bool res = false; if (parser->indent >= container->as.list.marker_offset + container->as.list.padding) { S_advance_offset(parser, input, container->as.list.marker_offset + container->as.list.padding, true); res = true; } else if (parser->blank && container->first_child != NULL) { // if container->first_child is NULL, then the opening line // of the list item was blank after the list marker; in this // case, we are done with the list item. S_advance_offset(parser, input, parser->first_nonspace - parser->offset, false); res = true; } return res; } static bool parse_code_block_prefix(cmark_parser *parser, cmark_chunk *input, cmark_node *container, bool *should_continue) { bool res = false; if (!container->as.code.fenced) { // indented if (parser->indent >= CODE_INDENT) { S_advance_offset(parser, input, CODE_INDENT, true); res = true; } else if (parser->blank) { S_advance_offset(parser, input, parser->first_nonspace - parser->offset, false); res = true; } } else { // fenced bufsize_t matched = 0; if (parser->indent <= 3 && (peek_at(input, parser->first_nonspace) == container->as.code.fence_char)) { matched = scan_close_code_fence(input, parser->first_nonspace); } if (matched >= container->as.code.fence_length) { // closing fence - and since we're at // the end of a line, we can stop processing it: *should_continue = false; S_advance_offset(parser, input, matched, false); parser->current = finalize(parser, container); } else { // skip opt. spaces of fence parser->offset int i = container->as.code.fence_offset; while (i > 0 && S_is_space_or_tab(peek_at(input, parser->offset))) { S_advance_offset(parser, input, 1, true); i--; } res = true; } } return res; } static bool parse_html_block_prefix(cmark_parser *parser, cmark_node *container) { bool res = false; int html_block_type = container->as.html_block_type; assert(html_block_type >= 1 && html_block_type <= 7); switch (html_block_type) { case 1: case 2: case 3: case 4: case 5: // these types of blocks can accept blanks res = true; break; case 6: case 7: res = !parser->blank; break; } return res; } static bool parse_extension_block(cmark_parser *parser, cmark_node *container, cmark_chunk *input) { bool res = false; if (container->extension->last_block_matches) { if (container->extension->last_block_matches( container->extension, parser, input->data, input->len, container)) res = true; } return res; } /** * For each containing node, try to parse the associated line start. * * Will not close unmatched blocks, as we may have a lazy continuation * line -> http://spec.commonmark.org/0.24/#lazy-continuation-line * * Returns: The last matching node, or NULL */ static cmark_node *check_open_blocks(cmark_parser *parser, cmark_chunk *input, bool *all_matched) { bool should_continue = true; *all_matched = false; cmark_node *container = parser->root; cmark_node_type cont_type; while (S_last_child_is_open(container)) { container = container->last_child; cont_type = S_type(container); S_find_first_nonspace(parser, input); if (container->extension) { if (!parse_extension_block(parser, container, input)) goto done; continue; } switch (cont_type) { case CMARK_NODE_BLOCK_QUOTE: if (!parse_block_quote_prefix(parser, input)) goto done; break; case CMARK_NODE_ITEM: if (!parse_node_item_prefix(parser, input, container)) goto done; break; case CMARK_NODE_CODE_BLOCK: if (!parse_code_block_prefix(parser, input, container, &should_continue)) goto done; break; case CMARK_NODE_HEADING: // a heading can never contain more than one line goto done; case CMARK_NODE_HTML_BLOCK: if (!parse_html_block_prefix(parser, container)) goto done; break; case CMARK_NODE_PARAGRAPH: if (parser->blank) goto done; break; case CMARK_NODE_FOOTNOTE_DEFINITION: if (!parse_footnote_definition_block_prefix(parser, input, container)) goto done; break; default: break; } } *all_matched = true; done: if (!*all_matched) { container = container->parent; // back up to last matching node } if (!should_continue) { container = NULL; } return container; } static void open_new_blocks(cmark_parser *parser, cmark_node **container, cmark_chunk *input, bool all_matched) { bool indented; cmark_list *data = NULL; bool maybe_lazy = S_type(parser->current) == CMARK_NODE_PARAGRAPH; cmark_node_type cont_type = S_type(*container); bufsize_t matched = 0; int lev = 0; bool save_partially_consumed_tab; int save_offset; int save_column; while (cont_type != CMARK_NODE_CODE_BLOCK && cont_type != CMARK_NODE_HTML_BLOCK) { S_find_first_nonspace(parser, input); indented = parser->indent >= CODE_INDENT; if (!indented && peek_at(input, parser->first_nonspace) == '>') { bufsize_t blockquote_startpos = parser->first_nonspace; S_advance_offset(parser, input, parser->first_nonspace + 1 - parser->offset, false); // optional following character if (S_is_space_or_tab(peek_at(input, parser->offset))) { S_advance_offset(parser, input, 1, true); } *container = add_child(parser, *container, CMARK_NODE_BLOCK_QUOTE, blockquote_startpos + 1); } else if (!indented && (matched = scan_atx_heading_start( input, parser->first_nonspace))) { bufsize_t hashpos; int level = 0; bufsize_t heading_startpos = parser->first_nonspace; S_advance_offset(parser, input, parser->first_nonspace + matched - parser->offset, false); *container = add_child(parser, *container, CMARK_NODE_HEADING, heading_startpos + 1); hashpos = cmark_chunk_strchr(input, '#', parser->first_nonspace); while (peek_at(input, hashpos) == '#') { level++; hashpos++; } (*container)->as.heading.level = level; (*container)->as.heading.setext = false; (*container)->internal_offset = matched; } else if (!indented && (matched = scan_open_code_fence( input, parser->first_nonspace))) { *container = add_child(parser, *container, CMARK_NODE_CODE_BLOCK, parser->first_nonspace + 1); (*container)->as.code.fenced = true; (*container)->as.code.fence_char = peek_at(input, parser->first_nonspace); (*container)->as.code.fence_length = (matched > 255) ? 255 : (uint8_t)matched; (*container)->as.code.fence_offset = (int8_t)(parser->first_nonspace - parser->offset); (*container)->as.code.info = cmark_chunk_literal(""); S_advance_offset(parser, input, parser->first_nonspace + matched - parser->offset, false); } else if (!indented && ((matched = scan_html_block_start( input, parser->first_nonspace)) || (cont_type != CMARK_NODE_PARAGRAPH && (matched = scan_html_block_start_7( input, parser->first_nonspace))))) { *container = add_child(parser, *container, CMARK_NODE_HTML_BLOCK, parser->first_nonspace + 1); (*container)->as.html_block_type = matched; // note, we don't adjust parser->offset because the tag is part of the // text } else if (!indented && cont_type == CMARK_NODE_PARAGRAPH && (lev = scan_setext_heading_line(input, parser->first_nonspace))) { (*container)->type = (uint16_t)CMARK_NODE_HEADING; (*container)->as.heading.level = lev; (*container)->as.heading.setext = true; S_advance_offset(parser, input, input->len - 1 - parser->offset, false); } else if (!indented && !(cont_type == CMARK_NODE_PARAGRAPH && !all_matched) && (matched = scan_thematic_break(input, parser->first_nonspace))) { // it's only now that we know the line is not part of a setext heading: *container = add_child(parser, *container, CMARK_NODE_THEMATIC_BREAK, parser->first_nonspace + 1); S_advance_offset(parser, input, input->len - 1 - parser->offset, false); } else if (!indented && parser->options & CMARK_OPT_FOOTNOTES && (matched = scan_footnote_definition(input, parser->first_nonspace))) { cmark_chunk c = cmark_chunk_dup(input, parser->first_nonspace + 2, matched - 2); cmark_chunk_to_cstr(parser->mem, &c); while (c.data[c.len - 1] != ']') --c.len; --c.len; S_advance_offset(parser, input, parser->first_nonspace + matched - parser->offset, false); *container = add_child(parser, *container, CMARK_NODE_FOOTNOTE_DEFINITION, parser->first_nonspace + matched + 1); (*container)->as.literal = c; (*container)->internal_offset = matched; } else if ((!indented || cont_type == CMARK_NODE_LIST) && parser->indent < 4 && (matched = parse_list_marker( parser->mem, input, parser->first_nonspace, (*container)->type == CMARK_NODE_PARAGRAPH, &data))) { // Note that we can have new list items starting with >= 4 // spaces indent, as long as the list container is still open. int i = 0; // compute padding: S_advance_offset(parser, input, parser->first_nonspace + matched - parser->offset, false); save_partially_consumed_tab = parser->partially_consumed_tab; save_offset = parser->offset; save_column = parser->column; while (parser->column - save_column <= 5 && S_is_space_or_tab(peek_at(input, parser->offset))) { S_advance_offset(parser, input, 1, true); } i = parser->column - save_column; if (i >= 5 || i < 1 || // only spaces after list marker: S_is_line_end_char(peek_at(input, parser->offset))) { data->padding = matched + 1; parser->offset = save_offset; parser->column = save_column; parser->partially_consumed_tab = save_partially_consumed_tab; if (i > 0) { S_advance_offset(parser, input, 1, true); } } else { data->padding = matched + i; } // check container; if it's a list, see if this list item // can continue the list; otherwise, create a list container. data->marker_offset = parser->indent; if (cont_type != CMARK_NODE_LIST || !lists_match(&((*container)->as.list), data)) { *container = add_child(parser, *container, CMARK_NODE_LIST, parser->first_nonspace + 1); memcpy(&((*container)->as.list), data, sizeof(*data)); } // add the list item *container = add_child(parser, *container, CMARK_NODE_ITEM, parser->first_nonspace + 1); /* TODO: static */ memcpy(&((*container)->as.list), data, sizeof(*data)); parser->mem->free(data); } else if (indented && !maybe_lazy && !parser->blank) { S_advance_offset(parser, input, CODE_INDENT, true); *container = add_child(parser, *container, CMARK_NODE_CODE_BLOCK, parser->offset + 1); (*container)->as.code.fenced = false; (*container)->as.code.fence_char = 0; (*container)->as.code.fence_length = 0; (*container)->as.code.fence_offset = 0; (*container)->as.code.info = cmark_chunk_literal(""); } else { cmark_llist *tmp; cmark_node *new_container = NULL; for (tmp = parser->syntax_extensions; tmp; tmp=tmp->next) { cmark_syntax_extension *ext = (cmark_syntax_extension *) tmp->data; if (ext->try_opening_block) { new_container = ext->try_opening_block( ext, indented, parser, *container, input->data, input->len); if (new_container) { *container = new_container; break; } } } if (!new_container) { break; } } if (accepts_lines(S_type(*container))) { // if it's a line container, it can't contain other containers break; } cont_type = S_type(*container); maybe_lazy = false; } } static void add_text_to_container(cmark_parser *parser, cmark_node *container, cmark_node *last_matched_container, cmark_chunk *input) { cmark_node *tmp; // what remains at parser->offset is a text line. add the text to the // appropriate container. S_find_first_nonspace(parser, input); if (parser->blank && container->last_child) S_set_last_line_blank(container->last_child, true); // block quote lines are never blank as they start with > // and we don't count blanks in fenced code for purposes of tight/loose // lists or breaking out of lists. we also don't set last_line_blank // on an empty list item. const cmark_node_type ctype = S_type(container); const bool last_line_blank = (parser->blank && ctype != CMARK_NODE_BLOCK_QUOTE && ctype != CMARK_NODE_HEADING && ctype != CMARK_NODE_THEMATIC_BREAK && !(ctype == CMARK_NODE_CODE_BLOCK && container->as.code.fenced) && !(ctype == CMARK_NODE_ITEM && container->first_child == NULL && container->start_line == parser->line_number)); S_set_last_line_blank(container, last_line_blank); tmp = container; while (tmp->parent) { S_set_last_line_blank(tmp->parent, false); tmp = tmp->parent; } // If the last line processed belonged to a paragraph node, // and we didn't match all of the line prefixes for the open containers, // and we didn't start any new containers, // and the line isn't blank, // then treat this as a "lazy continuation line" and add it to // the open paragraph. if (parser->current != last_matched_container && container == last_matched_container && !parser->blank && S_type(parser->current) == CMARK_NODE_PARAGRAPH) { add_line(parser->current, input, parser); } else { // not a lazy continuation // Finalize any blocks that were not matched and set cur to container: while (parser->current != last_matched_container) { parser->current = finalize(parser, parser->current); assert(parser->current != NULL); } if (S_type(container) == CMARK_NODE_CODE_BLOCK) { add_line(container, input, parser); } else if (S_type(container) == CMARK_NODE_HTML_BLOCK) { add_line(container, input, parser); int matches_end_condition; switch (container->as.html_block_type) { case 1: // , , matches_end_condition = scan_html_block_end_1(input, parser->first_nonspace); break; case 2: // --> matches_end_condition = scan_html_block_end_2(input, parser->first_nonspace); break; case 3: // ?> matches_end_condition = scan_html_block_end_3(input, parser->first_nonspace); break; case 4: // > matches_end_condition = scan_html_block_end_4(input, parser->first_nonspace); break; case 5: // ]]> matches_end_condition = scan_html_block_end_5(input, parser->first_nonspace); break; default: matches_end_condition = 0; break; } if (matches_end_condition) { container = finalize(parser, container); assert(parser->current != NULL); } } else if (parser->blank) { // ??? do nothing } else if (accepts_lines(S_type(container))) { if (S_type(container) == CMARK_NODE_HEADING && container->as.heading.setext == false) { chop_trailing_hashtags(input); } S_advance_offset(parser, input, parser->first_nonspace - parser->offset, false); add_line(container, input, parser); } else { // create paragraph container for line container = add_child(parser, container, CMARK_NODE_PARAGRAPH, parser->first_nonspace + 1); S_advance_offset(parser, input, parser->first_nonspace - parser->offset, false); add_line(container, input, parser); } parser->current = container; } } /* See http://spec.commonmark.org/0.24/#phase-1-block-structure */ static void S_process_line(cmark_parser *parser, const unsigned char *buffer, bufsize_t bytes) { cmark_node *last_matched_container; bool all_matched = true; cmark_node *container; cmark_chunk input; cmark_node *current; cmark_strbuf_clear(&parser->curline); if (parser->options & CMARK_OPT_VALIDATE_UTF8) cmark_utf8proc_check(&parser->curline, buffer, bytes); else cmark_strbuf_put(&parser->curline, buffer, bytes); bytes = parser->curline.size; // ensure line ends with a newline: if (bytes == 0 || !S_is_line_end_char(parser->curline.ptr[bytes - 1])) cmark_strbuf_putc(&parser->curline, '\n'); parser->offset = 0; parser->column = 0; parser->first_nonspace = 0; parser->first_nonspace_column = 0; parser->indent = 0; parser->blank = false; parser->partially_consumed_tab = false; input.data = parser->curline.ptr; input.len = parser->curline.size; input.alloc = 0; // Skip UTF-8 BOM. if (parser->line_number == 0 && input.len >= 3 && memcmp(input.data, "\xef\xbb\xbf", 3) == 0) parser->offset += 3; parser->line_number++; last_matched_container = check_open_blocks(parser, &input, &all_matched); if (!last_matched_container) goto finished; container = last_matched_container; current = parser->current; open_new_blocks(parser, &container, &input, all_matched); /* parser->current might have changed if feed_reentrant was called */ if (current == parser->current) add_text_to_container(parser, container, last_matched_container, &input); finished: parser->last_line_length = input.len; if (parser->last_line_length && input.data[parser->last_line_length - 1] == '\n') parser->last_line_length -= 1; if (parser->last_line_length && input.data[parser->last_line_length - 1] == '\r') parser->last_line_length -= 1; cmark_strbuf_clear(&parser->curline); } cmark_node *cmark_parser_finish(cmark_parser *parser) { cmark_node *res; cmark_llist *extensions; /* Parser was already finished once */ if (parser->root == NULL) return NULL; if (parser->linebuf.size) { S_process_line(parser, parser->linebuf.ptr, parser->linebuf.size); cmark_strbuf_clear(&parser->linebuf); } finalize_document(parser); cmark_consolidate_text_nodes(parser->root); cmark_strbuf_free(&parser->curline); cmark_strbuf_free(&parser->linebuf); #if CMARK_DEBUG_NODES if (cmark_node_check(parser->root, stderr)) { abort(); } #endif for (extensions = parser->syntax_extensions; extensions; extensions = extensions->next) { cmark_syntax_extension *ext = (cmark_syntax_extension *) extensions->data; if (ext->postprocess_func) { cmark_node *processed = ext->postprocess_func(ext, parser, parser->root); if (processed) parser->root = processed; } } res = parser->root; parser->root = NULL; cmark_parser_reset(parser); return res; } int cmark_parser_get_line_number(cmark_parser *parser) { return parser->line_number; } bufsize_t cmark_parser_get_offset(cmark_parser *parser) { return parser->offset; } bufsize_t cmark_parser_get_column(cmark_parser *parser) { return parser->column; } int cmark_parser_get_first_nonspace(cmark_parser *parser) { return parser->first_nonspace; } int cmark_parser_get_first_nonspace_column(cmark_parser *parser) { return parser->first_nonspace_column; } int cmark_parser_get_indent(cmark_parser *parser) { return parser->indent; } int cmark_parser_is_blank(cmark_parser *parser) { return parser->blank; } int cmark_parser_has_partially_consumed_tab(cmark_parser *parser) { return parser->partially_consumed_tab; } int cmark_parser_get_last_line_length(cmark_parser *parser) { return parser->last_line_length; } cmark_node *cmark_parser_add_child(cmark_parser *parser, cmark_node *parent, cmark_node_type block_type, int start_column) { return add_child(parser, parent, block_type, start_column); } void cmark_parser_advance_offset(cmark_parser *parser, const char *input, int count, int columns) { cmark_chunk input_chunk = cmark_chunk_literal(input); S_advance_offset(parser, &input_chunk, count, columns != 0); } void cmark_parser_set_backslash_ispunct_func(cmark_parser *parser, cmark_ispunct_func func) { parser->backslash_ispunct = func; } cmark_llist *cmark_parser_get_syntax_extensions(cmark_parser *parser) { return parser->syntax_extensions; } cmark-gfm-0.1.8/cbits/cmark.c0000644000000000000000000000244113442034251014116 0ustar0000000000000000#include #include #include #include "registry.h" #include "node.h" #include "houdini.h" #include "cmark-gfm.h" #include "buffer.h" cmark_node_type CMARK_NODE_LAST_BLOCK = CMARK_NODE_FOOTNOTE_DEFINITION; cmark_node_type CMARK_NODE_LAST_INLINE = CMARK_NODE_FOOTNOTE_REFERENCE; int cmark_version() { return CMARK_GFM_VERSION; } const char *cmark_version_string() { return CMARK_GFM_VERSION_STRING; } static void *xcalloc(size_t nmem, size_t size) { void *ptr = calloc(nmem, size); if (!ptr) { fprintf(stderr, "[cmark] calloc returned null pointer, aborting\n"); abort(); } return ptr; } static void *xrealloc(void *ptr, size_t size) { void *new_ptr = realloc(ptr, size); if (!new_ptr) { fprintf(stderr, "[cmark] realloc returned null pointer, aborting\n"); abort(); } return new_ptr; } static void xfree(void *ptr) { free(ptr); } cmark_mem CMARK_DEFAULT_MEM_ALLOCATOR = {xcalloc, xrealloc, xfree}; cmark_mem *cmark_get_default_mem_allocator() { return &CMARK_DEFAULT_MEM_ALLOCATOR; } char *cmark_markdown_to_html(const char *text, size_t len, int options) { cmark_node *doc; char *result; doc = cmark_parse_document(text, len, options); result = cmark_render_html(doc, options, NULL); cmark_node_free(doc); return result; } cmark-gfm-0.1.8/cbits/iterator.c0000644000000000000000000001054713442034251014660 0ustar0000000000000000#include #include #include "config.h" #include "node.h" #include "cmark-gfm.h" #include "iterator.h" cmark_iter *cmark_iter_new(cmark_node *root) { if (root == NULL) { return NULL; } cmark_mem *mem = root->content.mem; cmark_iter *iter = (cmark_iter *)mem->calloc(1, sizeof(cmark_iter)); iter->mem = mem; iter->root = root; iter->cur.ev_type = CMARK_EVENT_NONE; iter->cur.node = NULL; iter->next.ev_type = CMARK_EVENT_ENTER; iter->next.node = root; return iter; } void cmark_iter_free(cmark_iter *iter) { iter->mem->free(iter); } static bool S_is_leaf(cmark_node *node) { switch (node->type) { case CMARK_NODE_HTML_BLOCK: case CMARK_NODE_THEMATIC_BREAK: case CMARK_NODE_CODE_BLOCK: case CMARK_NODE_TEXT: case CMARK_NODE_SOFTBREAK: case CMARK_NODE_LINEBREAK: case CMARK_NODE_CODE: case CMARK_NODE_HTML_INLINE: return 1; } return 0; } cmark_event_type cmark_iter_next(cmark_iter *iter) { cmark_event_type ev_type = iter->next.ev_type; cmark_node *node = iter->next.node; iter->cur.ev_type = ev_type; iter->cur.node = node; if (ev_type == CMARK_EVENT_DONE) { return ev_type; } /* roll forward to next item, setting both fields */ if (ev_type == CMARK_EVENT_ENTER && !S_is_leaf(node)) { if (node->first_child == NULL) { /* stay on this node but exit */ iter->next.ev_type = CMARK_EVENT_EXIT; } else { iter->next.ev_type = CMARK_EVENT_ENTER; iter->next.node = node->first_child; } } else if (node == iter->root) { /* don't move past root */ iter->next.ev_type = CMARK_EVENT_DONE; iter->next.node = NULL; } else if (node->next) { iter->next.ev_type = CMARK_EVENT_ENTER; iter->next.node = node->next; } else if (node->parent) { iter->next.ev_type = CMARK_EVENT_EXIT; iter->next.node = node->parent; } else { assert(false); iter->next.ev_type = CMARK_EVENT_DONE; iter->next.node = NULL; } return ev_type; } void cmark_iter_reset(cmark_iter *iter, cmark_node *current, cmark_event_type event_type) { iter->next.ev_type = event_type; iter->next.node = current; cmark_iter_next(iter); } cmark_node *cmark_iter_get_node(cmark_iter *iter) { return iter->cur.node; } cmark_event_type cmark_iter_get_event_type(cmark_iter *iter) { return iter->cur.ev_type; } cmark_node *cmark_iter_get_root(cmark_iter *iter) { return iter->root; } void cmark_consolidate_text_nodes(cmark_node *root) { if (root == NULL) { return; } cmark_iter *iter = cmark_iter_new(root); cmark_strbuf buf = CMARK_BUF_INIT(iter->mem); cmark_event_type ev_type; cmark_node *cur, *tmp, *next; while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); if (ev_type == CMARK_EVENT_ENTER && cur->type == CMARK_NODE_TEXT && cur->next && cur->next->type == CMARK_NODE_TEXT) { cmark_strbuf_clear(&buf); cmark_strbuf_put(&buf, cur->as.literal.data, cur->as.literal.len); tmp = cur->next; while (tmp && tmp->type == CMARK_NODE_TEXT) { cmark_iter_next(iter); // advance pointer cmark_strbuf_put(&buf, tmp->as.literal.data, tmp->as.literal.len); cur->end_column = tmp->end_column; next = tmp->next; cmark_node_free(tmp); tmp = next; } cmark_chunk_free(iter->mem, &cur->as.literal); cur->as.literal = cmark_chunk_buf_detach(&buf); } } cmark_strbuf_free(&buf); cmark_iter_free(iter); } void cmark_node_own(cmark_node *root) { if (root == NULL) { return; } cmark_iter *iter = cmark_iter_new(root); cmark_event_type ev_type; cmark_node *cur; while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); if (ev_type == CMARK_EVENT_ENTER) { switch (cur->type) { case CMARK_NODE_TEXT: case CMARK_NODE_HTML_INLINE: case CMARK_NODE_CODE: case CMARK_NODE_HTML_BLOCK: cmark_chunk_to_cstr(iter->mem, &cur->as.literal); break; case CMARK_NODE_LINK: cmark_chunk_to_cstr(iter->mem, &cur->as.link.url); cmark_chunk_to_cstr(iter->mem, &cur->as.link.title); break; case CMARK_NODE_CUSTOM_INLINE: cmark_chunk_to_cstr(iter->mem, &cur->as.custom.on_enter); cmark_chunk_to_cstr(iter->mem, &cur->as.custom.on_exit); break; } } } cmark_iter_free(iter); } cmark-gfm-0.1.8/cbits/node.c0000644000000000000000000005034513442034251013754 0ustar0000000000000000#include #include #include "config.h" #include "node.h" #include "syntax_extension.h" static void S_node_unlink(cmark_node *node); #define NODE_MEM(node) cmark_node_mem(node) bool cmark_node_can_contain_type(cmark_node *node, cmark_node_type child_type) { if (child_type == CMARK_NODE_DOCUMENT) { return false; } if (node->extension && node->extension->can_contain_func) { return node->extension->can_contain_func(node->extension, node, child_type) != 0; } switch (node->type) { case CMARK_NODE_DOCUMENT: case CMARK_NODE_BLOCK_QUOTE: case CMARK_NODE_FOOTNOTE_DEFINITION: case CMARK_NODE_ITEM: return CMARK_NODE_TYPE_BLOCK_P(child_type) && child_type != CMARK_NODE_ITEM; case CMARK_NODE_LIST: return child_type == CMARK_NODE_ITEM; case CMARK_NODE_CUSTOM_BLOCK: return true; case CMARK_NODE_PARAGRAPH: case CMARK_NODE_HEADING: case CMARK_NODE_EMPH: case CMARK_NODE_STRONG: case CMARK_NODE_LINK: case CMARK_NODE_IMAGE: case CMARK_NODE_CUSTOM_INLINE: return CMARK_NODE_TYPE_INLINE_P(child_type); default: break; } return false; } static bool S_can_contain(cmark_node *node, cmark_node *child) { cmark_node *cur; if (node == NULL || child == NULL) { return false; } if (NODE_MEM(node) != NODE_MEM(child)) { return 0; } // Verify that child is not an ancestor of node or equal to node. cur = node; do { if (cur == child) { return false; } cur = cur->parent; } while (cur != NULL); return cmark_node_can_contain_type(node, (cmark_node_type) child->type); } cmark_node *cmark_node_new_with_mem_and_ext(cmark_node_type type, cmark_mem *mem, cmark_syntax_extension *extension) { cmark_node *node = (cmark_node *)mem->calloc(1, sizeof(*node)); cmark_strbuf_init(mem, &node->content, 0); node->type = (uint16_t)type; node->extension = extension; switch (node->type) { case CMARK_NODE_HEADING: node->as.heading.level = 1; break; case CMARK_NODE_LIST: { cmark_list *list = &node->as.list; list->list_type = CMARK_BULLET_LIST; list->start = 0; list->tight = false; break; } default: break; } if (node->extension && node->extension->opaque_alloc_func) { node->extension->opaque_alloc_func(node->extension, mem, node); } return node; } cmark_node *cmark_node_new_with_ext(cmark_node_type type, cmark_syntax_extension *extension) { extern cmark_mem CMARK_DEFAULT_MEM_ALLOCATOR; return cmark_node_new_with_mem_and_ext(type, &CMARK_DEFAULT_MEM_ALLOCATOR, extension); } cmark_node *cmark_node_new_with_mem(cmark_node_type type, cmark_mem *mem) { return cmark_node_new_with_mem_and_ext(type, mem, NULL); } cmark_node *cmark_node_new(cmark_node_type type) { return cmark_node_new_with_ext(type, NULL); } static void free_node_as(cmark_node *node) { switch (node->type) { case CMARK_NODE_CODE_BLOCK: cmark_chunk_free(NODE_MEM(node), &node->as.code.info); cmark_chunk_free(NODE_MEM(node), &node->as.code.literal); break; case CMARK_NODE_TEXT: case CMARK_NODE_HTML_INLINE: case CMARK_NODE_CODE: case CMARK_NODE_HTML_BLOCK: case CMARK_NODE_FOOTNOTE_REFERENCE: case CMARK_NODE_FOOTNOTE_DEFINITION: cmark_chunk_free(NODE_MEM(node), &node->as.literal); break; case CMARK_NODE_LINK: case CMARK_NODE_IMAGE: cmark_chunk_free(NODE_MEM(node), &node->as.link.url); cmark_chunk_free(NODE_MEM(node), &node->as.link.title); break; case CMARK_NODE_CUSTOM_BLOCK: case CMARK_NODE_CUSTOM_INLINE: cmark_chunk_free(NODE_MEM(node), &node->as.custom.on_enter); cmark_chunk_free(NODE_MEM(node), &node->as.custom.on_exit); break; default: break; } } // Free a cmark_node list and any children. static void S_free_nodes(cmark_node *e) { cmark_node *next; while (e != NULL) { cmark_strbuf_free(&e->content); if (e->user_data && e->user_data_free_func) e->user_data_free_func(NODE_MEM(e), e->user_data); if (e->as.opaque && e->extension && e->extension->opaque_free_func) e->extension->opaque_free_func(e->extension, NODE_MEM(e), e); free_node_as(e); if (e->last_child) { // Splice children into list e->last_child->next = e->next; e->next = e->first_child; } next = e->next; NODE_MEM(e)->free(e); e = next; } } void cmark_node_free(cmark_node *node) { S_node_unlink(node); node->next = NULL; S_free_nodes(node); } cmark_node_type cmark_node_get_type(cmark_node *node) { if (node == NULL) { return CMARK_NODE_NONE; } else { return (cmark_node_type)node->type; } } int cmark_node_set_type(cmark_node * node, cmark_node_type type) { cmark_node_type initial_type; if (type == node->type) return 1; initial_type = (cmark_node_type) node->type; node->type = (uint16_t)type; if (!S_can_contain(node->parent, node)) { node->type = (uint16_t)initial_type; return 0; } /* We rollback the type to free the union members appropriately */ node->type = (uint16_t)initial_type; free_node_as(node); node->type = (uint16_t)type; return 1; } const char *cmark_node_get_type_string(cmark_node *node) { if (node == NULL) { return "NONE"; } if (node->extension && node->extension->get_type_string_func) { return node->extension->get_type_string_func(node->extension, node); } switch (node->type) { case CMARK_NODE_NONE: return "none"; case CMARK_NODE_DOCUMENT: return "document"; case CMARK_NODE_BLOCK_QUOTE: return "block_quote"; case CMARK_NODE_LIST: return "list"; case CMARK_NODE_ITEM: return "item"; case CMARK_NODE_CODE_BLOCK: return "code_block"; case CMARK_NODE_HTML_BLOCK: return "html_block"; case CMARK_NODE_CUSTOM_BLOCK: return "custom_block"; case CMARK_NODE_PARAGRAPH: return "paragraph"; case CMARK_NODE_HEADING: return "heading"; case CMARK_NODE_THEMATIC_BREAK: return "thematic_break"; case CMARK_NODE_TEXT: return "text"; case CMARK_NODE_SOFTBREAK: return "softbreak"; case CMARK_NODE_LINEBREAK: return "linebreak"; case CMARK_NODE_CODE: return "code"; case CMARK_NODE_HTML_INLINE: return "html_inline"; case CMARK_NODE_CUSTOM_INLINE: return "custom_inline"; case CMARK_NODE_EMPH: return "emph"; case CMARK_NODE_STRONG: return "strong"; case CMARK_NODE_LINK: return "link"; case CMARK_NODE_IMAGE: return "image"; } return ""; } cmark_node *cmark_node_next(cmark_node *node) { if (node == NULL) { return NULL; } else { return node->next; } } cmark_node *cmark_node_previous(cmark_node *node) { if (node == NULL) { return NULL; } else { return node->prev; } } cmark_node *cmark_node_parent(cmark_node *node) { if (node == NULL) { return NULL; } else { return node->parent; } } cmark_node *cmark_node_first_child(cmark_node *node) { if (node == NULL) { return NULL; } else { return node->first_child; } } cmark_node *cmark_node_last_child(cmark_node *node) { if (node == NULL) { return NULL; } else { return node->last_child; } } void *cmark_node_get_user_data(cmark_node *node) { if (node == NULL) { return NULL; } else { return node->user_data; } } int cmark_node_set_user_data(cmark_node *node, void *user_data) { if (node == NULL) { return 0; } node->user_data = user_data; return 1; } int cmark_node_set_user_data_free_func(cmark_node *node, cmark_free_func free_func) { if (node == NULL) { return 0; } node->user_data_free_func = free_func; return 1; } const char *cmark_node_get_literal(cmark_node *node) { if (node == NULL) { return NULL; } switch (node->type) { case CMARK_NODE_HTML_BLOCK: case CMARK_NODE_TEXT: case CMARK_NODE_HTML_INLINE: case CMARK_NODE_CODE: case CMARK_NODE_FOOTNOTE_REFERENCE: return cmark_chunk_to_cstr(NODE_MEM(node), &node->as.literal); case CMARK_NODE_CODE_BLOCK: return cmark_chunk_to_cstr(NODE_MEM(node), &node->as.code.literal); default: break; } return NULL; } int cmark_node_set_literal(cmark_node *node, const char *content) { if (node == NULL) { return 0; } switch (node->type) { case CMARK_NODE_HTML_BLOCK: case CMARK_NODE_TEXT: case CMARK_NODE_HTML_INLINE: case CMARK_NODE_CODE: case CMARK_NODE_FOOTNOTE_REFERENCE: cmark_chunk_set_cstr(NODE_MEM(node), &node->as.literal, content); return 1; case CMARK_NODE_CODE_BLOCK: cmark_chunk_set_cstr(NODE_MEM(node), &node->as.code.literal, content); return 1; default: break; } return 0; } const char *cmark_node_get_string_content(cmark_node *node) { return (char *) node->content.ptr; } int cmark_node_set_string_content(cmark_node *node, const char *content) { cmark_strbuf_sets(&node->content, content); return true; } int cmark_node_get_heading_level(cmark_node *node) { if (node == NULL) { return 0; } switch (node->type) { case CMARK_NODE_HEADING: return node->as.heading.level; default: break; } return 0; } int cmark_node_set_heading_level(cmark_node *node, int level) { if (node == NULL || level < 1 || level > 6) { return 0; } switch (node->type) { case CMARK_NODE_HEADING: node->as.heading.level = level; return 1; default: break; } return 0; } cmark_list_type cmark_node_get_list_type(cmark_node *node) { if (node == NULL) { return CMARK_NO_LIST; } if (node->type == CMARK_NODE_LIST) { return node->as.list.list_type; } else { return CMARK_NO_LIST; } } int cmark_node_set_list_type(cmark_node *node, cmark_list_type type) { if (!(type == CMARK_BULLET_LIST || type == CMARK_ORDERED_LIST)) { return 0; } if (node == NULL) { return 0; } if (node->type == CMARK_NODE_LIST) { node->as.list.list_type = type; return 1; } else { return 0; } } cmark_delim_type cmark_node_get_list_delim(cmark_node *node) { if (node == NULL) { return CMARK_NO_DELIM; } if (node->type == CMARK_NODE_LIST) { return node->as.list.delimiter; } else { return CMARK_NO_DELIM; } } int cmark_node_set_list_delim(cmark_node *node, cmark_delim_type delim) { if (!(delim == CMARK_PERIOD_DELIM || delim == CMARK_PAREN_DELIM)) { return 0; } if (node == NULL) { return 0; } if (node->type == CMARK_NODE_LIST) { node->as.list.delimiter = delim; return 1; } else { return 0; } } int cmark_node_get_list_start(cmark_node *node) { if (node == NULL) { return 0; } if (node->type == CMARK_NODE_LIST) { return node->as.list.start; } else { return 0; } } int cmark_node_set_list_start(cmark_node *node, int start) { if (node == NULL || start < 0) { return 0; } if (node->type == CMARK_NODE_LIST) { node->as.list.start = start; return 1; } else { return 0; } } int cmark_node_get_list_tight(cmark_node *node) { if (node == NULL) { return 0; } if (node->type == CMARK_NODE_LIST) { return node->as.list.tight; } else { return 0; } } int cmark_node_set_list_tight(cmark_node *node, int tight) { if (node == NULL) { return 0; } if (node->type == CMARK_NODE_LIST) { node->as.list.tight = tight == 1; return 1; } else { return 0; } } const char *cmark_node_get_fence_info(cmark_node *node) { if (node == NULL) { return NULL; } if (node->type == CMARK_NODE_CODE_BLOCK) { return cmark_chunk_to_cstr(NODE_MEM(node), &node->as.code.info); } else { return NULL; } } int cmark_node_set_fence_info(cmark_node *node, const char *info) { if (node == NULL) { return 0; } if (node->type == CMARK_NODE_CODE_BLOCK) { cmark_chunk_set_cstr(NODE_MEM(node), &node->as.code.info, info); return 1; } else { return 0; } } int cmark_node_get_fenced(cmark_node *node, int *length, int *offset, char *character) { if (node == NULL) { return 0; } if (node->type == CMARK_NODE_CODE_BLOCK) { *length = node->as.code.fence_length; *offset = node->as.code.fence_offset; *character = node->as.code.fence_char; return node->as.code.fenced; } else { return 0; } } int cmark_node_set_fenced(cmark_node * node, int fenced, int length, int offset, char character) { if (node == NULL) { return 0; } if (node->type == CMARK_NODE_CODE_BLOCK) { node->as.code.fenced = (int8_t)fenced; node->as.code.fence_length = (uint8_t)length; node->as.code.fence_offset = (uint8_t)offset; node->as.code.fence_char = character; return 1; } else { return 0; } } const char *cmark_node_get_url(cmark_node *node) { if (node == NULL) { return NULL; } switch (node->type) { case CMARK_NODE_LINK: case CMARK_NODE_IMAGE: return cmark_chunk_to_cstr(NODE_MEM(node), &node->as.link.url); default: break; } return NULL; } int cmark_node_set_url(cmark_node *node, const char *url) { if (node == NULL) { return 0; } switch (node->type) { case CMARK_NODE_LINK: case CMARK_NODE_IMAGE: cmark_chunk_set_cstr(NODE_MEM(node), &node->as.link.url, url); return 1; default: break; } return 0; } const char *cmark_node_get_title(cmark_node *node) { if (node == NULL) { return NULL; } switch (node->type) { case CMARK_NODE_LINK: case CMARK_NODE_IMAGE: return cmark_chunk_to_cstr(NODE_MEM(node), &node->as.link.title); default: break; } return NULL; } int cmark_node_set_title(cmark_node *node, const char *title) { if (node == NULL) { return 0; } switch (node->type) { case CMARK_NODE_LINK: case CMARK_NODE_IMAGE: cmark_chunk_set_cstr(NODE_MEM(node), &node->as.link.title, title); return 1; default: break; } return 0; } const char *cmark_node_get_on_enter(cmark_node *node) { if (node == NULL) { return NULL; } switch (node->type) { case CMARK_NODE_CUSTOM_INLINE: case CMARK_NODE_CUSTOM_BLOCK: return cmark_chunk_to_cstr(NODE_MEM(node), &node->as.custom.on_enter); default: break; } return NULL; } int cmark_node_set_on_enter(cmark_node *node, const char *on_enter) { if (node == NULL) { return 0; } switch (node->type) { case CMARK_NODE_CUSTOM_INLINE: case CMARK_NODE_CUSTOM_BLOCK: cmark_chunk_set_cstr(NODE_MEM(node), &node->as.custom.on_enter, on_enter); return 1; default: break; } return 0; } const char *cmark_node_get_on_exit(cmark_node *node) { if (node == NULL) { return NULL; } switch (node->type) { case CMARK_NODE_CUSTOM_INLINE: case CMARK_NODE_CUSTOM_BLOCK: return cmark_chunk_to_cstr(NODE_MEM(node), &node->as.custom.on_exit); default: break; } return NULL; } int cmark_node_set_on_exit(cmark_node *node, const char *on_exit) { if (node == NULL) { return 0; } switch (node->type) { case CMARK_NODE_CUSTOM_INLINE: case CMARK_NODE_CUSTOM_BLOCK: cmark_chunk_set_cstr(NODE_MEM(node), &node->as.custom.on_exit, on_exit); return 1; default: break; } return 0; } cmark_syntax_extension *cmark_node_get_syntax_extension(cmark_node *node) { if (node == NULL) { return NULL; } return node->extension; } int cmark_node_set_syntax_extension(cmark_node *node, cmark_syntax_extension *extension) { if (node == NULL) { return 0; } node->extension = extension; return 1; } int cmark_node_get_start_line(cmark_node *node) { if (node == NULL) { return 0; } return node->start_line; } int cmark_node_get_start_column(cmark_node *node) { if (node == NULL) { return 0; } return node->start_column; } int cmark_node_get_end_line(cmark_node *node) { if (node == NULL) { return 0; } return node->end_line; } int cmark_node_get_end_column(cmark_node *node) { if (node == NULL) { return 0; } return node->end_column; } // Unlink a node without adjusting its next, prev, and parent pointers. static void S_node_unlink(cmark_node *node) { if (node == NULL) { return; } if (node->prev) { node->prev->next = node->next; } if (node->next) { node->next->prev = node->prev; } // Adjust first_child and last_child of parent. cmark_node *parent = node->parent; if (parent) { if (parent->first_child == node) { parent->first_child = node->next; } if (parent->last_child == node) { parent->last_child = node->prev; } } } void cmark_node_unlink(cmark_node *node) { S_node_unlink(node); node->next = NULL; node->prev = NULL; node->parent = NULL; } int cmark_node_insert_before(cmark_node *node, cmark_node *sibling) { if (node == NULL || sibling == NULL) { return 0; } if (!node->parent || !S_can_contain(node->parent, sibling)) { return 0; } S_node_unlink(sibling); cmark_node *old_prev = node->prev; // Insert 'sibling' between 'old_prev' and 'node'. if (old_prev) { old_prev->next = sibling; } sibling->prev = old_prev; sibling->next = node; node->prev = sibling; // Set new parent. cmark_node *parent = node->parent; sibling->parent = parent; // Adjust first_child of parent if inserted as first child. if (parent && !old_prev) { parent->first_child = sibling; } return 1; } int cmark_node_insert_after(cmark_node *node, cmark_node *sibling) { if (node == NULL || sibling == NULL) { return 0; } if (!node->parent || !S_can_contain(node->parent, sibling)) { return 0; } S_node_unlink(sibling); cmark_node *old_next = node->next; // Insert 'sibling' between 'node' and 'old_next'. if (old_next) { old_next->prev = sibling; } sibling->next = old_next; sibling->prev = node; node->next = sibling; // Set new parent. cmark_node *parent = node->parent; sibling->parent = parent; // Adjust last_child of parent if inserted as last child. if (parent && !old_next) { parent->last_child = sibling; } return 1; } int cmark_node_replace(cmark_node *oldnode, cmark_node *newnode) { if (!cmark_node_insert_before(oldnode, newnode)) { return 0; } cmark_node_unlink(oldnode); return 1; } int cmark_node_prepend_child(cmark_node *node, cmark_node *child) { if (!S_can_contain(node, child)) { return 0; } S_node_unlink(child); cmark_node *old_first_child = node->first_child; child->next = old_first_child; child->prev = NULL; child->parent = node; node->first_child = child; if (old_first_child) { old_first_child->prev = child; } else { // Also set last_child if node previously had no children. node->last_child = child; } return 1; } int cmark_node_append_child(cmark_node *node, cmark_node *child) { if (!S_can_contain(node, child)) { return 0; } S_node_unlink(child); cmark_node *old_last_child = node->last_child; child->next = NULL; child->prev = old_last_child; child->parent = node; node->last_child = child; if (old_last_child) { old_last_child->next = child; } else { // Also set first_child if node previously had no children. node->first_child = child; } return 1; } static void S_print_error(FILE *out, cmark_node *node, const char *elem) { if (out == NULL) { return; } fprintf(out, "Invalid '%s' in node type %s at %d:%d\n", elem, cmark_node_get_type_string(node), node->start_line, node->start_column); } int cmark_node_check(cmark_node *node, FILE *out) { cmark_node *cur; int errors = 0; if (!node) { return 0; } cur = node; for (;;) { if (cur->first_child) { if (cur->first_child->prev != NULL) { S_print_error(out, cur->first_child, "prev"); cur->first_child->prev = NULL; ++errors; } if (cur->first_child->parent != cur) { S_print_error(out, cur->first_child, "parent"); cur->first_child->parent = cur; ++errors; } cur = cur->first_child; continue; } next_sibling: if (cur == node) { break; } if (cur->next) { if (cur->next->prev != cur) { S_print_error(out, cur->next, "prev"); cur->next->prev = cur; ++errors; } if (cur->next->parent != cur->parent) { S_print_error(out, cur->next, "parent"); cur->next->parent = cur->parent; ++errors; } cur = cur->next; continue; } if (cur->parent->last_child != cur) { S_print_error(out, cur->parent, "last_child"); cur->parent->last_child = cur; ++errors; } cur = cur->parent; goto next_sibling; } return errors; } cmark-gfm-0.1.8/cbits/buffer.c0000644000000000000000000001460313442034251014275 0ustar0000000000000000#include #include #include #include #include #include #include #include #include "config.h" #include "cmark_ctype.h" #include "buffer.h" #include "memory.h" /* Used as default value for cmark_strbuf->ptr so that people can always * assume ptr is non-NULL and zero terminated even for new cmark_strbufs. */ unsigned char cmark_strbuf__initbuf[1]; #ifndef MIN #define MIN(x, y) ((x < y) ? x : y) #endif void cmark_strbuf_init(cmark_mem *mem, cmark_strbuf *buf, bufsize_t initial_size) { buf->mem = mem; buf->asize = 0; buf->size = 0; buf->ptr = cmark_strbuf__initbuf; if (initial_size > 0) cmark_strbuf_grow(buf, initial_size); } static CMARK_INLINE void S_strbuf_grow_by(cmark_strbuf *buf, bufsize_t add) { cmark_strbuf_grow(buf, buf->size + add); } void cmark_strbuf_grow(cmark_strbuf *buf, bufsize_t target_size) { assert(target_size > 0); if (target_size < buf->asize) return; if (target_size > (bufsize_t)(INT32_MAX / 2)) { fprintf(stderr, "[cmark] cmark_strbuf_grow requests buffer with size > %d, aborting\n", (INT32_MAX / 2)); abort(); } /* Oversize the buffer by 50% to guarantee amortized linear time * complexity on append operations. */ bufsize_t new_size = target_size + target_size / 2; new_size += 1; new_size = (new_size + 7) & ~7; buf->ptr = (unsigned char *)buf->mem->realloc(buf->asize ? buf->ptr : NULL, new_size); buf->asize = new_size; } bufsize_t cmark_strbuf_len(const cmark_strbuf *buf) { return buf->size; } void cmark_strbuf_free(cmark_strbuf *buf) { if (!buf) return; if (buf->ptr != cmark_strbuf__initbuf) buf->mem->free(buf->ptr); cmark_strbuf_init(buf->mem, buf, 0); } void cmark_strbuf_clear(cmark_strbuf *buf) { buf->size = 0; if (buf->asize > 0) buf->ptr[0] = '\0'; } void cmark_strbuf_set(cmark_strbuf *buf, const unsigned char *data, bufsize_t len) { if (len <= 0 || data == NULL) { cmark_strbuf_clear(buf); } else { if (data != buf->ptr) { if (len >= buf->asize) cmark_strbuf_grow(buf, len); memmove(buf->ptr, data, len); } buf->size = len; buf->ptr[buf->size] = '\0'; } } void cmark_strbuf_sets(cmark_strbuf *buf, const char *string) { cmark_strbuf_set(buf, (const unsigned char *)string, string ? (bufsize_t)strlen(string) : 0); } void cmark_strbuf_putc(cmark_strbuf *buf, int c) { S_strbuf_grow_by(buf, 1); buf->ptr[buf->size++] = (unsigned char)(c & 0xFF); buf->ptr[buf->size] = '\0'; } void cmark_strbuf_put(cmark_strbuf *buf, const unsigned char *data, bufsize_t len) { if (len <= 0) return; S_strbuf_grow_by(buf, len); memmove(buf->ptr + buf->size, data, len); buf->size += len; buf->ptr[buf->size] = '\0'; } void cmark_strbuf_puts(cmark_strbuf *buf, const char *string) { cmark_strbuf_put(buf, (const unsigned char *)string, (bufsize_t)strlen(string)); } void cmark_strbuf_copy_cstr(char *data, bufsize_t datasize, const cmark_strbuf *buf) { bufsize_t copylen; assert(buf); if (!data || datasize <= 0) return; data[0] = '\0'; if (buf->size == 0 || buf->asize <= 0) return; copylen = buf->size; if (copylen > datasize - 1) copylen = datasize - 1; memmove(data, buf->ptr, copylen); data[copylen] = '\0'; } void cmark_strbuf_swap(cmark_strbuf *buf_a, cmark_strbuf *buf_b) { cmark_strbuf t = *buf_a; *buf_a = *buf_b; *buf_b = t; } unsigned char *cmark_strbuf_detach(cmark_strbuf *buf) { unsigned char *data = buf->ptr; if (buf->asize == 0) { /* return an empty string */ return (unsigned char *)buf->mem->calloc(1, 1); } cmark_strbuf_init(buf->mem, buf, 0); return data; } int cmark_strbuf_cmp(const cmark_strbuf *a, const cmark_strbuf *b) { int result = memcmp(a->ptr, b->ptr, MIN(a->size, b->size)); return (result != 0) ? result : (a->size < b->size) ? -1 : (a->size > b->size) ? 1 : 0; } bufsize_t cmark_strbuf_strchr(const cmark_strbuf *buf, int c, bufsize_t pos) { if (pos >= buf->size) return -1; if (pos < 0) pos = 0; const unsigned char *p = (unsigned char *)memchr(buf->ptr + pos, c, buf->size - pos); if (!p) return -1; return (bufsize_t)(p - (const unsigned char *)buf->ptr); } bufsize_t cmark_strbuf_strrchr(const cmark_strbuf *buf, int c, bufsize_t pos) { if (pos < 0 || buf->size == 0) return -1; if (pos >= buf->size) pos = buf->size - 1; bufsize_t i; for (i = pos; i >= 0; i--) { if (buf->ptr[i] == (unsigned char)c) return i; } return -1; } void cmark_strbuf_truncate(cmark_strbuf *buf, bufsize_t len) { if (len < 0) len = 0; if (len < buf->size) { buf->size = len; buf->ptr[buf->size] = '\0'; } } void cmark_strbuf_drop(cmark_strbuf *buf, bufsize_t n) { if (n > 0) { if (n > buf->size) n = buf->size; buf->size = buf->size - n; if (buf->size) memmove(buf->ptr, buf->ptr + n, buf->size); buf->ptr[buf->size] = '\0'; } } void cmark_strbuf_rtrim(cmark_strbuf *buf) { if (!buf->size) return; while (buf->size > 0) { if (!cmark_isspace(buf->ptr[buf->size - 1])) break; buf->size--; } buf->ptr[buf->size] = '\0'; } void cmark_strbuf_trim(cmark_strbuf *buf) { bufsize_t i = 0; if (!buf->size) return; while (i < buf->size && cmark_isspace(buf->ptr[i])) i++; cmark_strbuf_drop(buf, i); cmark_strbuf_rtrim(buf); } // Destructively modify string, collapsing consecutive // space and newline characters into a single space. void cmark_strbuf_normalize_whitespace(cmark_strbuf *s) { bool last_char_was_space = false; bufsize_t r, w; for (r = 0, w = 0; r < s->size; ++r) { if (cmark_isspace(s->ptr[r])) { if (!last_char_was_space) { s->ptr[w++] = ' '; last_char_was_space = true; } } else { s->ptr[w++] = s->ptr[r]; last_char_was_space = false; } } cmark_strbuf_truncate(s, w); } // Destructively unescape a string: remove backslashes before punctuation chars. extern void cmark_strbuf_unescape(cmark_strbuf *buf) { bufsize_t r, w; for (r = 0, w = 0; r < buf->size; ++r) { if (buf->ptr[r] == '\\' && cmark_ispunct(buf->ptr[r + 1])) r++; buf->ptr[w++] = buf->ptr[r]; } cmark_strbuf_truncate(buf, w); } cmark-gfm-0.1.8/cbits/cmark_ctype.c0000644000000000000000000000332113361532163015325 0ustar0000000000000000#include #include "cmark_ctype.h" /** 1 = space, 2 = punct, 3 = digit, 4 = alpha, 0 = other */ static const uint8_t cmark_ctype_class[256] = { /* 0 1 2 3 4 5 6 7 8 9 a b c d e f */ /* 0 */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 0, 0, 1, 0, 0, /* 1 */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* 2 */ 1, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, /* 3 */ 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 2, 2, 2, 2, 2, 2, /* 4 */ 2, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, /* 5 */ 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 2, 2, 2, 2, 2, /* 6 */ 2, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, /* 7 */ 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 4, 2, 2, 2, 2, 0, /* 8 */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* 9 */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* a */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* b */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* c */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* d */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* e */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* f */ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0}; /** * Returns 1 if c is a "whitespace" character as defined by the spec. */ int cmark_isspace(char c) { return cmark_ctype_class[(uint8_t)c] == 1; } /** * Returns 1 if c is an ascii punctuation character. */ int cmark_ispunct(char c) { return cmark_ctype_class[(uint8_t)c] == 2; } int cmark_isalnum(char c) { uint8_t result; result = cmark_ctype_class[(uint8_t)c]; return (result == 3 || result == 4); } int cmark_isdigit(char c) { return cmark_ctype_class[(uint8_t)c] == 3; } int cmark_isalpha(char c) { return cmark_ctype_class[(uint8_t)c] == 4; } cmark-gfm-0.1.8/cbits/houdini_html_e.c0000644000000000000000000000406013442034251016007 0ustar0000000000000000#include #include #include #include "houdini.h" /** * According to the OWASP rules: * * & --> & * < --> < * > --> > * " --> " * ' --> ' ' is not recommended * / --> / forward slash is included as it helps end an HTML entity * */ static const char HTML_ESCAPE_TABLE[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 2, 3, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; static const char *HTML_ESCAPES[] = {"", """, "&", "'", "/", "<", ">"}; int houdini_escape_html0(cmark_strbuf *ob, const uint8_t *src, bufsize_t size, int secure) { bufsize_t i = 0, org, esc = 0; while (i < size) { org = i; while (i < size && (esc = HTML_ESCAPE_TABLE[src[i]]) == 0) i++; if (i > org) cmark_strbuf_put(ob, src + org, i - org); /* escaping */ if (unlikely(i >= size)) break; /* The forward slash and single quote are only escaped in secure mode */ if ((src[i] == '/' || src[i] == '\'') && !secure) { cmark_strbuf_putc(ob, src[i]); } else { cmark_strbuf_puts(ob, HTML_ESCAPES[esc]); } i++; } return 1; } int houdini_escape_html(cmark_strbuf *ob, const uint8_t *src, bufsize_t size) { return houdini_escape_html0(ob, src, size, 1); } cmark-gfm-0.1.8/cbits/houdini_href_e.c0000644000000000000000000000570713442037162016004 0ustar0000000000000000#include #include #include #include "houdini.h" /* * The following characters will not be escaped: * * -_.+!*'(),%#@?=;:/,+&$~ alphanum * * Note that this character set is the addition of: * * - The characters which are safe to be in an URL * - The characters which are *not* safe to be in * an URL because they are RESERVED characters. * * We assume (lazily) that any RESERVED char that * appears inside an URL is actually meant to * have its native function (i.e. as an URL * component/separator) and hence needs no escaping. * * There are two exceptions: the chacters & (amp) * and ' (single quote) do not appear in the table. * They are meant to appear in the URL as components, * yet they require special HTML-entity escaping * to generate valid HTML markup. * * All other characters will be escaped to %XX. * */ static const char HREF_SAFE[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 1, 1, 1, 0, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 1, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 1, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; int houdini_escape_href(cmark_strbuf *ob, const uint8_t *src, bufsize_t size) { static const uint8_t hex_chars[] = "0123456789ABCDEF"; bufsize_t i = 0, org; uint8_t hex_str[3]; hex_str[0] = '%'; while (i < size) { org = i; while (i < size && HREF_SAFE[src[i]] != 0) i++; if (likely(i > org)) cmark_strbuf_put(ob, src + org, i - org); /* escaping */ if (i >= size) break; switch (src[i]) { /* amp appears all the time in URLs, but needs * HTML-entity escaping to be inside an href */ case '&': cmark_strbuf_puts(ob, "&"); break; /* the single quote is a valid URL character * according to the standard; it needs HTML * entity escaping too */ case '\'': cmark_strbuf_puts(ob, "'"); break; /* the space can be escaped to %20 or a plus * sign. we're going with the generic escape * for now. the plus thing is more commonly seen * when building GET strings */ #if 0 case ' ': cmark_strbuf_putc(ob, '+'); break; #endif /* every other character goes with a %XX escaping */ default: hex_str[1] = hex_chars[(src[i] >> 4) & 0xF]; hex_str[2] = hex_chars[src[i] & 0xF]; cmark_strbuf_put(ob, hex_str, 3); } i++; } return 1; } cmark-gfm-0.1.8/cbits/scanners.c0000644000000000000000000064351513442037162014656 0ustar0000000000000000/* Generated by re2c 1.1.1 */ #include #include "chunk.h" #include "scanners.h" bufsize_t _scan_at(bufsize_t (*scanner)(const unsigned char *), cmark_chunk *c, bufsize_t offset) { bufsize_t res; unsigned char *ptr = (unsigned char *)c->data; if (ptr == NULL || offset > c->len) { return 0; } else { unsigned char lim = ptr[c->len]; ptr[c->len] = '\0'; res = scanner(ptr + offset); ptr[c->len] = lim; } return res; } // Try to match a scheme including colon. bufsize_t _scan_scheme(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; yych = *p; if (yych <= '@') goto yy2; if (yych <= 'Z') goto yy4; if (yych <= '`') goto yy2; if (yych <= 'z') goto yy4; yy2: ++p; yy3: { return 0; } yy4: yych = *(marker = ++p); if (yych <= '/') { if (yych <= '+') { if (yych <= '*') goto yy3; } else { if (yych <= ',') goto yy3; if (yych >= '/') goto yy3; } } else { if (yych <= 'Z') { if (yych <= '9') goto yy5; if (yych <= '@') goto yy3; } else { if (yych <= '`') goto yy3; if (yych >= '{') goto yy3; } } yy5: yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych == '+') goto yy7; } else { if (yych != '/') goto yy7; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych >= 'A') goto yy7; } else { if (yych <= '`') goto yy6; if (yych <= 'z') goto yy7; } } yy6: p = marker; goto yy3; yy7: yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych == '+') goto yy10; goto yy6; } else { if (yych == '/') goto yy6; goto yy10; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; goto yy10; } else { if (yych <= '`') goto yy6; if (yych <= 'z') goto yy10; goto yy6; } } yy8: ++p; { return (bufsize_t)(p - start); } yy10: yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy6; } else { if (yych == '/') goto yy6; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy8; if (yych <= '@') goto yy6; } else { if (yych <= '`') goto yy6; if (yych >= '{') goto yy6; } } yych = *++p; if (yych == ':') goto yy8; goto yy6; } } // Try to match URI autolink after first <, returning number of chars matched. bufsize_t _scan_autolink_uri(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 128, 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= '@') goto yy41; if (yych <= 'Z') goto yy43; if (yych <= '`') goto yy41; if (yych <= 'z') goto yy43; yy41: ++p; yy42: { return 0; } yy43: yych = *(marker = ++p); if (yych <= '/') { if (yych <= '+') { if (yych <= '*') goto yy42; } else { if (yych <= ',') goto yy42; if (yych >= '/') goto yy42; } } else { if (yych <= 'Z') { if (yych <= '9') goto yy44; if (yych <= '@') goto yy42; } else { if (yych <= '`') goto yy42; if (yych >= '{') goto yy42; } } yy44: yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych == '+') goto yy46; } else { if (yych != '/') goto yy46; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych >= 'A') goto yy46; } else { if (yych <= '`') goto yy45; if (yych <= 'z') goto yy46; } } yy45: p = marker; goto yy42; yy46: yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych == '+') goto yy49; goto yy45; } else { if (yych == '/') goto yy45; goto yy49; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; goto yy49; } else { if (yych <= '`') goto yy45; if (yych <= 'z') goto yy49; goto yy45; } } yy47: yych = *++p; if (yybm[0+yych] & 128) { goto yy47; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '<') goto yy45; if (yych <= '>') goto yy50; goto yy45; } else { if (yych <= 0xDF) goto yy52; if (yych <= 0xE0) goto yy53; goto yy54; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy55; if (yych <= 0xEF) goto yy54; goto yy56; } else { if (yych <= 0xF3) goto yy57; if (yych <= 0xF4) goto yy58; goto yy45; } } yy49: yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych == '+') goto yy59; goto yy45; } else { if (yych == '/') goto yy45; goto yy59; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; goto yy59; } else { if (yych <= '`') goto yy45; if (yych <= 'z') goto yy59; goto yy45; } } yy50: ++p; { return (bufsize_t)(p - start); } yy52: yych = *++p; if (yych <= 0x7F) goto yy45; if (yych <= 0xBF) goto yy47; goto yy45; yy53: yych = *++p; if (yych <= 0x9F) goto yy45; if (yych <= 0xBF) goto yy52; goto yy45; yy54: yych = *++p; if (yych <= 0x7F) goto yy45; if (yych <= 0xBF) goto yy52; goto yy45; yy55: yych = *++p; if (yych <= 0x7F) goto yy45; if (yych <= 0x9F) goto yy52; goto yy45; yy56: yych = *++p; if (yych <= 0x8F) goto yy45; if (yych <= 0xBF) goto yy54; goto yy45; yy57: yych = *++p; if (yych <= 0x7F) goto yy45; if (yych <= 0xBF) goto yy54; goto yy45; yy58: yych = *++p; if (yych <= 0x7F) goto yy45; if (yych <= 0x8F) goto yy54; goto yy45; yy59: yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych <= '9') { if (yych <= ',') { if (yych != '+') goto yy45; } else { if (yych == '/') goto yy45; } } else { if (yych <= 'Z') { if (yych <= ':') goto yy47; if (yych <= '@') goto yy45; } else { if (yych <= '`') goto yy45; if (yych >= '{') goto yy45; } } yych = *++p; if (yych == ':') goto yy47; goto yy45; } } // Try to match email autolink after first <, returning num of chars matched. bufsize_t _scan_autolink_email(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 128, 128, 128, 128, 128, 0, 0, 128, 128, 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 0, 0, 128, 0, 128, 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 0, 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= '9') { if (yych <= '\'') { if (yych == '!') goto yy91; if (yych >= '#') goto yy91; } else { if (yych <= ')') goto yy89; if (yych != ',') goto yy91; } } else { if (yych <= '?') { if (yych == '=') goto yy91; if (yych >= '?') goto yy91; } else { if (yych <= 'Z') { if (yych >= 'A') goto yy91; } else { if (yych <= ']') goto yy89; if (yych <= '~') goto yy91; } } } yy89: ++p; yy90: { return 0; } yy91: yych = *(marker = ++p); if (yych <= ',') { if (yych <= '"') { if (yych == '!') goto yy93; goto yy90; } else { if (yych <= '\'') goto yy93; if (yych <= ')') goto yy90; if (yych <= '+') goto yy93; goto yy90; } } else { if (yych <= '>') { if (yych <= '9') goto yy93; if (yych == '=') goto yy93; goto yy90; } else { if (yych <= 'Z') goto yy93; if (yych <= ']') goto yy90; if (yych <= '~') goto yy93; goto yy90; } } yy92: yych = *++p; yy93: if (yybm[0+yych] & 128) { goto yy92; } if (yych <= '>') goto yy94; if (yych <= '@') goto yy95; yy94: p = marker; goto yy90; yy95: yych = *++p; if (yych <= '@') { if (yych <= '/') goto yy94; if (yych >= ':') goto yy94; } else { if (yych <= 'Z') goto yy96; if (yych <= '`') goto yy94; if (yych >= '{') goto yy94; } yy96: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy98; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy98; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy98; goto yy94; } } yych = *++p; if (yych <= '9') { if (yych == '-') goto yy101; if (yych <= '/') goto yy94; goto yy102; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy102; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy102; goto yy94; } } yy98: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych <= '-') goto yy101; goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy102; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy102; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy102; goto yy94; } } yy99: ++p; { return (bufsize_t)(p - start); } yy101: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy103; if (yych <= '/') goto yy94; goto yy104; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy104; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy104; goto yy94; } } yy102: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy104; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy104; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy104; goto yy94; } } yy103: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy105; if (yych <= '/') goto yy94; goto yy106; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy106; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy106; goto yy94; } } yy104: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy106; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy106; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy106; goto yy94; } } yy105: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy107; if (yych <= '/') goto yy94; goto yy108; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy108; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy108; goto yy94; } } yy106: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy108; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy108; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy108; goto yy94; } } yy107: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy109; if (yych <= '/') goto yy94; goto yy110; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy110; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy110; goto yy94; } } yy108: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy110; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy110; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy110; goto yy94; } } yy109: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy111; if (yych <= '/') goto yy94; goto yy112; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy112; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy112; goto yy94; } } yy110: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy112; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy112; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy112; goto yy94; } } yy111: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy113; if (yych <= '/') goto yy94; goto yy114; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy114; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy114; goto yy94; } } yy112: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy114; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy114; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy114; goto yy94; } } yy113: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy115; if (yych <= '/') goto yy94; goto yy116; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy116; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy116; goto yy94; } } yy114: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy116; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy116; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy116; goto yy94; } } yy115: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy117; if (yych <= '/') goto yy94; goto yy118; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy118; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy118; goto yy94; } } yy116: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy118; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy118; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy118; goto yy94; } } yy117: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy119; if (yych <= '/') goto yy94; goto yy120; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy120; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy120; goto yy94; } } yy118: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy120; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy120; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy120; goto yy94; } } yy119: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy121; if (yych <= '/') goto yy94; goto yy122; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy122; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy122; goto yy94; } } yy120: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy122; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy122; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy122; goto yy94; } } yy121: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy123; if (yych <= '/') goto yy94; goto yy124; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy124; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy124; goto yy94; } } yy122: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy124; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy124; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy124; goto yy94; } } yy123: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy125; if (yych <= '/') goto yy94; goto yy126; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy126; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy126; goto yy94; } } yy124: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy126; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy126; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy126; goto yy94; } } yy125: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy127; if (yych <= '/') goto yy94; goto yy128; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy128; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy128; goto yy94; } } yy126: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy128; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy128; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy128; goto yy94; } } yy127: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy129; if (yych <= '/') goto yy94; goto yy130; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy130; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy130; goto yy94; } } yy128: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy130; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy130; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy130; goto yy94; } } yy129: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy131; if (yych <= '/') goto yy94; goto yy132; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy132; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy132; goto yy94; } } yy130: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy132; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy132; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy132; goto yy94; } } yy131: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy133; if (yych <= '/') goto yy94; goto yy134; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy134; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy134; goto yy94; } } yy132: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy134; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy134; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy134; goto yy94; } } yy133: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy135; if (yych <= '/') goto yy94; goto yy136; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy136; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy136; goto yy94; } } yy134: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy136; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy136; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy136; goto yy94; } } yy135: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy137; if (yych <= '/') goto yy94; goto yy138; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy138; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy138; goto yy94; } } yy136: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy138; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy138; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy138; goto yy94; } } yy137: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy139; if (yych <= '/') goto yy94; goto yy140; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy140; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy140; goto yy94; } } yy138: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy140; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy140; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy140; goto yy94; } } yy139: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy141; if (yych <= '/') goto yy94; goto yy142; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy142; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy142; goto yy94; } } yy140: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy142; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy142; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy142; goto yy94; } } yy141: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy143; if (yych <= '/') goto yy94; goto yy144; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy144; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy144; goto yy94; } } yy142: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy144; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy144; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy144; goto yy94; } } yy143: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy145; if (yych <= '/') goto yy94; goto yy146; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy146; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy146; goto yy94; } } yy144: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy146; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy146; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy146; goto yy94; } } yy145: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy147; if (yych <= '/') goto yy94; goto yy148; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy148; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy148; goto yy94; } } yy146: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy148; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy148; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy148; goto yy94; } } yy147: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy149; if (yych <= '/') goto yy94; goto yy150; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy150; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy150; goto yy94; } } yy148: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy150; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy150; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy150; goto yy94; } } yy149: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy151; if (yych <= '/') goto yy94; goto yy152; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy152; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy152; goto yy94; } } yy150: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy152; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy152; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy152; goto yy94; } } yy151: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy153; if (yych <= '/') goto yy94; goto yy154; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy154; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy154; goto yy94; } } yy152: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy154; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy154; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy154; goto yy94; } } yy153: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy155; if (yych <= '/') goto yy94; goto yy156; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy156; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy156; goto yy94; } } yy154: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy156; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy156; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy156; goto yy94; } } yy155: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy157; if (yych <= '/') goto yy94; goto yy158; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy158; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy158; goto yy94; } } yy156: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy158; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy158; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy158; goto yy94; } } yy157: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy159; if (yych <= '/') goto yy94; goto yy160; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy160; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy160; goto yy94; } } yy158: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy160; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy160; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy160; goto yy94; } } yy159: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy161; if (yych <= '/') goto yy94; goto yy162; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy162; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy162; goto yy94; } } yy160: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy162; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy162; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy162; goto yy94; } } yy161: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy163; if (yych <= '/') goto yy94; goto yy164; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy164; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy164; goto yy94; } } yy162: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy164; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy164; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy164; goto yy94; } } yy163: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy165; if (yych <= '/') goto yy94; goto yy166; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy166; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy166; goto yy94; } } yy164: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy166; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy166; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy166; goto yy94; } } yy165: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy167; if (yych <= '/') goto yy94; goto yy168; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy168; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy168; goto yy94; } } yy166: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy168; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy168; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy168; goto yy94; } } yy167: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy169; if (yych <= '/') goto yy94; goto yy170; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy170; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy170; goto yy94; } } yy168: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy170; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy170; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy170; goto yy94; } } yy169: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy171; if (yych <= '/') goto yy94; goto yy172; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy172; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy172; goto yy94; } } yy170: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy172; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy172; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy172; goto yy94; } } yy171: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy173; if (yych <= '/') goto yy94; goto yy174; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy174; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy174; goto yy94; } } yy172: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy174; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy174; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy174; goto yy94; } } yy173: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy175; if (yych <= '/') goto yy94; goto yy176; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy176; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy176; goto yy94; } } yy174: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy176; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy176; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy176; goto yy94; } } yy175: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy177; if (yych <= '/') goto yy94; goto yy178; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy178; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy178; goto yy94; } } yy176: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy178; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy178; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy178; goto yy94; } } yy177: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy179; if (yych <= '/') goto yy94; goto yy180; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy180; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy180; goto yy94; } } yy178: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy180; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy180; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy180; goto yy94; } } yy179: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy181; if (yych <= '/') goto yy94; goto yy182; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy182; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy182; goto yy94; } } yy180: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy182; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy182; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy182; goto yy94; } } yy181: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy183; if (yych <= '/') goto yy94; goto yy184; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy184; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy184; goto yy94; } } yy182: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy184; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy184; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy184; goto yy94; } } yy183: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy185; if (yych <= '/') goto yy94; goto yy186; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy186; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy186; goto yy94; } } yy184: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy186; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy186; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy186; goto yy94; } } yy185: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy187; if (yych <= '/') goto yy94; goto yy188; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy188; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy188; goto yy94; } } yy186: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy188; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy188; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy188; goto yy94; } } yy187: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy189; if (yych <= '/') goto yy94; goto yy190; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy190; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy190; goto yy94; } } yy188: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy190; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy190; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy190; goto yy94; } } yy189: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy191; if (yych <= '/') goto yy94; goto yy192; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy192; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy192; goto yy94; } } yy190: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy192; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy192; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy192; goto yy94; } } yy191: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy193; if (yych <= '/') goto yy94; goto yy194; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy194; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy194; goto yy94; } } yy192: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy194; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy194; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy194; goto yy94; } } yy193: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy195; if (yych <= '/') goto yy94; goto yy196; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy196; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy196; goto yy94; } } yy194: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy196; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy196; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy196; goto yy94; } } yy195: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy197; if (yych <= '/') goto yy94; goto yy198; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy198; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy198; goto yy94; } } yy196: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy198; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy198; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy198; goto yy94; } } yy197: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy199; if (yych <= '/') goto yy94; goto yy200; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy200; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy200; goto yy94; } } yy198: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy200; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy200; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy200; goto yy94; } } yy199: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy201; if (yych <= '/') goto yy94; goto yy202; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy202; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy202; goto yy94; } } yy200: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy202; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy202; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy202; goto yy94; } } yy201: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy203; if (yych <= '/') goto yy94; goto yy204; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy204; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy204; goto yy94; } } yy202: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy204; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy204; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy204; goto yy94; } } yy203: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy205; if (yych <= '/') goto yy94; goto yy206; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy206; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy206; goto yy94; } } yy204: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy206; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy206; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy206; goto yy94; } } yy205: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy207; if (yych <= '/') goto yy94; goto yy208; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy208; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy208; goto yy94; } } yy206: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy208; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy208; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy208; goto yy94; } } yy207: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy209; if (yych <= '/') goto yy94; goto yy210; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy210; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy210; goto yy94; } } yy208: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy210; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy210; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy210; goto yy94; } } yy209: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy211; if (yych <= '/') goto yy94; goto yy212; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy212; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy212; goto yy94; } } yy210: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy212; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy212; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy212; goto yy94; } } yy211: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy213; if (yych <= '/') goto yy94; goto yy214; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy214; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy214; goto yy94; } } yy212: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy214; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy214; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy214; goto yy94; } } yy213: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy215; if (yych <= '/') goto yy94; goto yy216; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy216; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy216; goto yy94; } } yy214: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy216; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy216; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy216; goto yy94; } } yy215: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy217; if (yych <= '/') goto yy94; goto yy218; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy218; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy218; goto yy94; } } yy216: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy218; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy218; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy218; goto yy94; } } yy217: yych = *++p; if (yych <= '9') { if (yych == '-') goto yy219; if (yych <= '/') goto yy94; goto yy220; } else { if (yych <= 'Z') { if (yych <= '@') goto yy94; goto yy220; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy220; goto yy94; } } yy218: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= ',') goto yy94; if (yych >= '.') goto yy95; } else { if (yych <= '/') goto yy94; if (yych <= '9') goto yy220; goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; goto yy220; } else { if (yych <= '`') goto yy94; if (yych <= 'z') goto yy220; goto yy94; } } yy219: yych = *++p; if (yych <= '@') { if (yych <= '/') goto yy94; if (yych <= '9') goto yy221; goto yy94; } else { if (yych <= 'Z') goto yy221; if (yych <= '`') goto yy94; if (yych <= 'z') goto yy221; goto yy94; } yy220: yych = *++p; if (yych <= '=') { if (yych <= '.') { if (yych <= '-') goto yy94; goto yy95; } else { if (yych <= '/') goto yy94; if (yych >= ':') goto yy94; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy99; if (yych <= '@') goto yy94; } else { if (yych <= '`') goto yy94; if (yych >= '{') goto yy94; } } yy221: yych = *++p; if (yych == '.') goto yy95; if (yych == '>') goto yy99; goto yy94; } } // Try to match an HTML tag after first <, returning num of chars matched. bufsize_t _scan_html_tag(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { /* table 1 .. 8: 0 */ 0, 250, 250, 250, 250, 250, 250, 250, 250, 235, 235, 235, 235, 235, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 250, 235, 250, 202, 250, 250, 250, 250, 170, 250, 250, 250, 250, 250, 246, 254, 250, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 250, 234, 234, 232, 250, 250, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 250, 250, 122, 250, 254, 234, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 254, 250, 250, 250, 250, 250, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, /* table 9 .. 11: 256 */ 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 192, 128, 128, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 128, 128, 128, 128, 128, 0, 128, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 128, 128, 128, 128, 128, 128, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 128, 128, 128, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= '>') { if (yych <= '!') { if (yych >= '!') goto yy226; } else { if (yych == '/') goto yy227; } } else { if (yych <= 'Z') { if (yych <= '?') goto yy228; if (yych >= 'A') goto yy229; } else { if (yych <= '`') goto yy224; if (yych <= 'z') goto yy229; } } yy224: ++p; yy225: { return 0; } yy226: yych = *(marker = ++p); if (yybm[256+yych] & 32) { goto yy232; } if (yych == '-') goto yy230; if (yych <= '@') goto yy225; if (yych <= '[') goto yy234; goto yy225; yy227: yych = *(marker = ++p); if (yych <= '@') goto yy225; if (yych <= 'Z') goto yy235; if (yych <= '`') goto yy225; if (yych <= 'z') goto yy235; goto yy225; yy228: yych = *(marker = ++p); if (yych <= 0x00) goto yy225; if (yych <= 0x7F) goto yy238; if (yych <= 0xC1) goto yy225; if (yych <= 0xF4) goto yy238; goto yy225; yy229: yych = *(marker = ++p); if (yych <= '.') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy225; if (yych <= '\r') goto yy250; goto yy225; } else { if (yych <= ' ') goto yy250; if (yych == '-') goto yy250; goto yy225; } } else { if (yych <= '@') { if (yych <= '9') goto yy250; if (yych == '>') goto yy250; goto yy225; } else { if (yych <= 'Z') goto yy250; if (yych <= '`') goto yy225; if (yych <= 'z') goto yy250; goto yy225; } } yy230: yych = *++p; if (yych == '-') goto yy254; yy231: p = marker; goto yy225; yy232: yych = *++p; if (yybm[256+yych] & 32) { goto yy232; } if (yych <= 0x08) goto yy231; if (yych <= '\r') goto yy255; if (yych == ' ') goto yy255; goto yy231; yy234: yych = *++p; if (yych == 'C') goto yy257; if (yych == 'c') goto yy257; goto yy231; yy235: yych = *++p; if (yybm[256+yych] & 64) { goto yy235; } if (yych <= 0x1F) { if (yych <= 0x08) goto yy231; if (yych <= '\r') goto yy258; goto yy231; } else { if (yych <= ' ') goto yy258; if (yych == '>') goto yy252; goto yy231; } yy237: yych = *++p; yy238: if (yybm[256+yych] & 128) { goto yy237; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych >= '@') goto yy231; } else { if (yych <= 0xDF) goto yy240; if (yych <= 0xE0) goto yy241; goto yy242; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy243; if (yych <= 0xEF) goto yy242; goto yy244; } else { if (yych <= 0xF3) goto yy245; if (yych <= 0xF4) goto yy246; goto yy231; } } yych = *++p; if (yych <= 0xE0) { if (yych <= '>') { if (yych <= 0x00) goto yy231; if (yych <= '=') goto yy237; goto yy252; } else { if (yych <= 0x7F) goto yy237; if (yych <= 0xC1) goto yy231; if (yych >= 0xE0) goto yy241; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy243; goto yy242; } else { if (yych <= 0xF0) goto yy244; if (yych <= 0xF3) goto yy245; if (yych <= 0xF4) goto yy246; goto yy231; } } yy240: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy237; goto yy231; yy241: yych = *++p; if (yych <= 0x9F) goto yy231; if (yych <= 0xBF) goto yy240; goto yy231; yy242: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy240; goto yy231; yy243: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x9F) goto yy240; goto yy231; yy244: yych = *++p; if (yych <= 0x8F) goto yy231; if (yych <= 0xBF) goto yy242; goto yy231; yy245: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy242; goto yy231; yy246: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x8F) goto yy242; goto yy231; yy247: yych = *++p; if (yybm[0+yych] & 1) { goto yy247; } if (yych <= '>') { if (yych <= '9') { if (yych == '/') goto yy251; goto yy231; } else { if (yych <= ':') goto yy260; if (yych <= '=') goto yy231; goto yy252; } } else { if (yych <= '^') { if (yych <= '@') goto yy231; if (yych <= 'Z') goto yy260; goto yy231; } else { if (yych == '`') goto yy231; if (yych <= 'z') goto yy260; goto yy231; } } yy249: yych = *++p; yy250: if (yybm[0+yych] & 1) { goto yy247; } if (yych <= '=') { if (yych <= '.') { if (yych == '-') goto yy249; goto yy231; } else { if (yych <= '/') goto yy251; if (yych <= '9') goto yy249; goto yy231; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy252; if (yych <= '@') goto yy231; goto yy249; } else { if (yych <= '`') goto yy231; if (yych <= 'z') goto yy249; goto yy231; } } yy251: yych = *++p; if (yych != '>') goto yy231; yy252: ++p; { return (bufsize_t)(p - start); } yy254: yych = *++p; if (yych == '-') goto yy264; if (yych == '>') goto yy231; goto yy263; yy255: yych = *++p; if (yybm[0+yych] & 2) { goto yy255; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych <= '>') goto yy252; goto yy231; } else { if (yych <= 0xDF) goto yy272; if (yych <= 0xE0) goto yy273; goto yy274; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy275; if (yych <= 0xEF) goto yy274; goto yy276; } else { if (yych <= 0xF3) goto yy277; if (yych <= 0xF4) goto yy278; goto yy231; } } yy257: yych = *++p; if (yych == 'D') goto yy279; if (yych == 'd') goto yy279; goto yy231; yy258: yych = *++p; if (yych <= 0x1F) { if (yych <= 0x08) goto yy231; if (yych <= '\r') goto yy258; goto yy231; } else { if (yych <= ' ') goto yy258; if (yych == '>') goto yy252; goto yy231; } yy260: yych = *++p; if (yybm[0+yych] & 4) { goto yy260; } if (yych <= ',') { if (yych <= '\r') { if (yych <= 0x08) goto yy231; goto yy280; } else { if (yych == ' ') goto yy280; goto yy231; } } else { if (yych <= '<') { if (yych <= '/') goto yy251; goto yy231; } else { if (yych <= '=') goto yy282; if (yych <= '>') goto yy252; goto yy231; } } yy262: yych = *++p; yy263: if (yybm[0+yych] & 8) { goto yy262; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych <= '-') goto yy284; goto yy231; } else { if (yych <= 0xDF) goto yy265; if (yych <= 0xE0) goto yy266; goto yy267; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy268; if (yych <= 0xEF) goto yy267; goto yy269; } else { if (yych <= 0xF3) goto yy270; if (yych <= 0xF4) goto yy271; goto yy231; } } yy264: yych = *++p; if (yych == '-') goto yy251; if (yych == '>') goto yy231; goto yy263; yy265: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy262; goto yy231; yy266: yych = *++p; if (yych <= 0x9F) goto yy231; if (yych <= 0xBF) goto yy265; goto yy231; yy267: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy265; goto yy231; yy268: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x9F) goto yy265; goto yy231; yy269: yych = *++p; if (yych <= 0x8F) goto yy231; if (yych <= 0xBF) goto yy267; goto yy231; yy270: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy267; goto yy231; yy271: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x8F) goto yy267; goto yy231; yy272: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy255; goto yy231; yy273: yych = *++p; if (yych <= 0x9F) goto yy231; if (yych <= 0xBF) goto yy272; goto yy231; yy274: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy272; goto yy231; yy275: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x9F) goto yy272; goto yy231; yy276: yych = *++p; if (yych <= 0x8F) goto yy231; if (yych <= 0xBF) goto yy274; goto yy231; yy277: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy274; goto yy231; yy278: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x8F) goto yy274; goto yy231; yy279: yych = *++p; if (yych == 'A') goto yy285; if (yych == 'a') goto yy285; goto yy231; yy280: yych = *++p; if (yych <= '<') { if (yych <= ' ') { if (yych <= 0x08) goto yy231; if (yych <= '\r') goto yy280; if (yych <= 0x1F) goto yy231; goto yy280; } else { if (yych <= '/') { if (yych <= '.') goto yy231; goto yy251; } else { if (yych == ':') goto yy260; goto yy231; } } } else { if (yych <= 'Z') { if (yych <= '=') goto yy282; if (yych <= '>') goto yy252; if (yych <= '@') goto yy231; goto yy260; } else { if (yych <= '_') { if (yych <= '^') goto yy231; goto yy260; } else { if (yych <= '`') goto yy231; if (yych <= 'z') goto yy260; goto yy231; } } } yy282: yych = *++p; if (yybm[0+yych] & 16) { goto yy286; } if (yych <= 0xE0) { if (yych <= '"') { if (yych <= 0x00) goto yy231; if (yych <= ' ') goto yy282; goto yy288; } else { if (yych <= '\'') goto yy290; if (yych <= 0xC1) goto yy231; if (yych <= 0xDF) goto yy292; goto yy293; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy295; goto yy294; } else { if (yych <= 0xF0) goto yy296; if (yych <= 0xF3) goto yy297; if (yych <= 0xF4) goto yy298; goto yy231; } } yy284: yych = *++p; if (yybm[0+yych] & 8) { goto yy262; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych <= '-') goto yy251; goto yy231; } else { if (yych <= 0xDF) goto yy265; if (yych <= 0xE0) goto yy266; goto yy267; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy268; if (yych <= 0xEF) goto yy267; goto yy269; } else { if (yych <= 0xF3) goto yy270; if (yych <= 0xF4) goto yy271; goto yy231; } } yy285: yych = *++p; if (yych == 'T') goto yy299; if (yych == 't') goto yy299; goto yy231; yy286: yych = *++p; if (yybm[0+yych] & 16) { goto yy286; } if (yych <= 0xE0) { if (yych <= '=') { if (yych <= 0x00) goto yy231; if (yych <= ' ') goto yy247; goto yy231; } else { if (yych <= '>') goto yy252; if (yych <= 0xC1) goto yy231; if (yych <= 0xDF) goto yy292; goto yy293; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy295; goto yy294; } else { if (yych <= 0xF0) goto yy296; if (yych <= 0xF3) goto yy297; if (yych <= 0xF4) goto yy298; goto yy231; } } yy288: yych = *++p; if (yybm[0+yych] & 32) { goto yy288; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych <= '"') goto yy300; goto yy231; } else { if (yych <= 0xDF) goto yy301; if (yych <= 0xE0) goto yy302; goto yy303; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy304; if (yych <= 0xEF) goto yy303; goto yy305; } else { if (yych <= 0xF3) goto yy306; if (yych <= 0xF4) goto yy307; goto yy231; } } yy290: yych = *++p; if (yybm[0+yych] & 64) { goto yy290; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych <= '\'') goto yy300; goto yy231; } else { if (yych <= 0xDF) goto yy308; if (yych <= 0xE0) goto yy309; goto yy310; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy311; if (yych <= 0xEF) goto yy310; goto yy312; } else { if (yych <= 0xF3) goto yy313; if (yych <= 0xF4) goto yy314; goto yy231; } } yy292: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy286; goto yy231; yy293: yych = *++p; if (yych <= 0x9F) goto yy231; if (yych <= 0xBF) goto yy292; goto yy231; yy294: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy292; goto yy231; yy295: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x9F) goto yy292; goto yy231; yy296: yych = *++p; if (yych <= 0x8F) goto yy231; if (yych <= 0xBF) goto yy294; goto yy231; yy297: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy294; goto yy231; yy298: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x8F) goto yy294; goto yy231; yy299: yych = *++p; if (yych == 'A') goto yy315; if (yych == 'a') goto yy315; goto yy231; yy300: yych = *++p; if (yybm[0+yych] & 1) { goto yy247; } if (yych == '/') goto yy251; if (yych == '>') goto yy252; goto yy231; yy301: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy288; goto yy231; yy302: yych = *++p; if (yych <= 0x9F) goto yy231; if (yych <= 0xBF) goto yy301; goto yy231; yy303: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy301; goto yy231; yy304: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x9F) goto yy301; goto yy231; yy305: yych = *++p; if (yych <= 0x8F) goto yy231; if (yych <= 0xBF) goto yy303; goto yy231; yy306: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy303; goto yy231; yy307: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x8F) goto yy303; goto yy231; yy308: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy290; goto yy231; yy309: yych = *++p; if (yych <= 0x9F) goto yy231; if (yych <= 0xBF) goto yy308; goto yy231; yy310: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy308; goto yy231; yy311: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x9F) goto yy308; goto yy231; yy312: yych = *++p; if (yych <= 0x8F) goto yy231; if (yych <= 0xBF) goto yy310; goto yy231; yy313: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy310; goto yy231; yy314: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x8F) goto yy310; goto yy231; yy315: yych = *++p; if (yych != '[') goto yy231; yy316: yych = *++p; if (yybm[0+yych] & 128) { goto yy316; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych >= '^') goto yy231; } else { if (yych <= 0xDF) goto yy319; if (yych <= 0xE0) goto yy320; goto yy321; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy322; if (yych <= 0xEF) goto yy321; goto yy323; } else { if (yych <= 0xF3) goto yy324; if (yych <= 0xF4) goto yy325; goto yy231; } } yych = *++p; if (yybm[0+yych] & 128) { goto yy316; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy231; if (yych <= ']') goto yy326; goto yy231; } else { if (yych <= 0xDF) goto yy319; if (yych <= 0xE0) goto yy320; goto yy321; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy322; if (yych <= 0xEF) goto yy321; goto yy323; } else { if (yych <= 0xF3) goto yy324; if (yych <= 0xF4) goto yy325; goto yy231; } } yy319: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy316; goto yy231; yy320: yych = *++p; if (yych <= 0x9F) goto yy231; if (yych <= 0xBF) goto yy319; goto yy231; yy321: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy319; goto yy231; yy322: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x9F) goto yy319; goto yy231; yy323: yych = *++p; if (yych <= 0x8F) goto yy231; if (yych <= 0xBF) goto yy321; goto yy231; yy324: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0xBF) goto yy321; goto yy231; yy325: yych = *++p; if (yych <= 0x7F) goto yy231; if (yych <= 0x8F) goto yy321; goto yy231; yy326: yych = *++p; if (yych <= 0xE0) { if (yych <= '>') { if (yych <= 0x00) goto yy231; if (yych <= '=') goto yy316; goto yy252; } else { if (yych <= 0x7F) goto yy316; if (yych <= 0xC1) goto yy231; if (yych <= 0xDF) goto yy319; goto yy320; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy322; goto yy321; } else { if (yych <= 0xF0) goto yy323; if (yych <= 0xF3) goto yy324; if (yych <= 0xF4) goto yy325; goto yy231; } } } } // Try to (liberally) match an HTML tag after first <, returning num of chars matched. bufsize_t _scan_liberal_html_tag(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 128, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= 0xE0) { if (yych <= '\n') { if (yych <= 0x00) goto yy329; if (yych <= '\t') goto yy331; } else { if (yych <= 0x7F) goto yy331; if (yych <= 0xC1) goto yy329; if (yych <= 0xDF) goto yy332; goto yy333; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy335; goto yy334; } else { if (yych <= 0xF0) goto yy336; if (yych <= 0xF3) goto yy337; if (yych <= 0xF4) goto yy338; } } yy329: ++p; yy330: { return 0; } yy331: yyaccept = 0; yych = *(marker = ++p); if (yych <= '\n') { if (yych <= 0x00) goto yy330; if (yych <= '\t') goto yy340; goto yy330; } else { if (yych <= 0x7F) goto yy340; if (yych <= 0xC1) goto yy330; if (yych <= 0xF4) goto yy340; goto yy330; } yy332: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy330; if (yych <= 0xBF) goto yy339; goto yy330; yy333: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x9F) goto yy330; if (yych <= 0xBF) goto yy345; goto yy330; yy334: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy330; if (yych <= 0xBF) goto yy345; goto yy330; yy335: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy330; if (yych <= 0x9F) goto yy345; goto yy330; yy336: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x8F) goto yy330; if (yych <= 0xBF) goto yy347; goto yy330; yy337: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy330; if (yych <= 0xBF) goto yy347; goto yy330; yy338: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy330; if (yych <= 0x8F) goto yy347; goto yy330; yy339: yych = *++p; yy340: if (yybm[0+yych] & 64) { goto yy339; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy341; if (yych <= '>') goto yy342; } else { if (yych <= 0xDF) goto yy345; if (yych <= 0xE0) goto yy346; goto yy347; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy348; if (yych <= 0xEF) goto yy347; goto yy349; } else { if (yych <= 0xF3) goto yy350; if (yych <= 0xF4) goto yy351; } } yy341: p = marker; if (yyaccept == 0) { goto yy330; } else { goto yy344; } yy342: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 64) { goto yy339; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy344; if (yych <= '>') goto yy342; } else { if (yych <= 0xDF) goto yy345; if (yych <= 0xE0) goto yy346; goto yy347; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy348; if (yych <= 0xEF) goto yy347; goto yy349; } else { if (yych <= 0xF3) goto yy350; if (yych <= 0xF4) goto yy351; } } yy344: { return (bufsize_t)(p - start); } yy345: yych = *++p; if (yych <= 0x7F) goto yy341; if (yych <= 0xBF) goto yy339; goto yy341; yy346: yych = *++p; if (yych <= 0x9F) goto yy341; if (yych <= 0xBF) goto yy345; goto yy341; yy347: yych = *++p; if (yych <= 0x7F) goto yy341; if (yych <= 0xBF) goto yy345; goto yy341; yy348: yych = *++p; if (yych <= 0x7F) goto yy341; if (yych <= 0x9F) goto yy345; goto yy341; yy349: yych = *++p; if (yych <= 0x8F) goto yy341; if (yych <= 0xBF) goto yy347; goto yy341; yy350: yych = *++p; if (yych <= 0x7F) goto yy341; if (yych <= 0xBF) goto yy347; goto yy341; yy351: yych = *++p; if (yych <= 0x7F) goto yy341; if (yych <= 0x8F) goto yy347; goto yy341; } } // Try to match an HTML block tag start line, returning // an integer code for the type of block (1-6, matching the spec). // #7 is handled by a separate function, below. bufsize_t _scan_html_block_start(const unsigned char *p) { const unsigned char *marker = NULL; { unsigned char yych; yych = *p; if (yych == '<') goto yy356; ++p; yy355: { return 0; } yy356: yych = *(marker = ++p); switch (yych) { case '!': goto yy357; case '/': goto yy359; case '?': goto yy360; case 'A': case 'a': goto yy362; case 'B': case 'b': goto yy363; case 'C': case 'c': goto yy364; case 'D': case 'd': goto yy365; case 'F': case 'f': goto yy366; case 'H': case 'h': goto yy367; case 'I': case 'i': goto yy368; case 'L': case 'l': goto yy369; case 'M': case 'm': goto yy370; case 'N': case 'n': goto yy371; case 'O': case 'o': goto yy372; case 'P': case 'p': goto yy373; case 'S': case 's': goto yy374; case 'T': case 't': goto yy375; case 'U': case 'u': goto yy376; default: goto yy355; } yy357: yych = *++p; if (yych <= '@') { if (yych == '-') goto yy377; } else { if (yych <= 'Z') goto yy378; if (yych <= '[') goto yy380; } yy358: p = marker; goto yy355; yy359: yych = *++p; switch (yych) { case 'A': case 'a': goto yy362; case 'B': case 'b': goto yy363; case 'C': case 'c': goto yy364; case 'D': case 'd': goto yy365; case 'F': case 'f': goto yy366; case 'H': case 'h': goto yy367; case 'I': case 'i': goto yy368; case 'L': case 'l': goto yy369; case 'M': case 'm': goto yy370; case 'N': case 'n': goto yy371; case 'O': case 'o': goto yy372; case 'P': case 'p': goto yy381; case 'S': case 's': goto yy382; case 'T': case 't': goto yy375; case 'U': case 'u': goto yy376; default: goto yy358; } yy360: ++p; { return 3; } yy362: yych = *++p; if (yych <= 'S') { if (yych <= 'D') { if (yych <= 'C') goto yy358; goto yy383; } else { if (yych <= 'Q') goto yy358; if (yych <= 'R') goto yy384; goto yy385; } } else { if (yych <= 'q') { if (yych == 'd') goto yy383; goto yy358; } else { if (yych <= 'r') goto yy384; if (yych <= 's') goto yy385; goto yy358; } } yy363: yych = *++p; if (yych <= 'O') { if (yych <= 'K') { if (yych == 'A') goto yy386; goto yy358; } else { if (yych <= 'L') goto yy387; if (yych <= 'N') goto yy358; goto yy388; } } else { if (yych <= 'k') { if (yych == 'a') goto yy386; goto yy358; } else { if (yych <= 'l') goto yy387; if (yych == 'o') goto yy388; goto yy358; } } yy364: yych = *++p; if (yych <= 'O') { if (yych <= 'D') { if (yych == 'A') goto yy389; goto yy358; } else { if (yych <= 'E') goto yy390; if (yych <= 'N') goto yy358; goto yy391; } } else { if (yych <= 'd') { if (yych == 'a') goto yy389; goto yy358; } else { if (yych <= 'e') goto yy390; if (yych == 'o') goto yy391; goto yy358; } } yy365: yych = *++p; switch (yych) { case 'D': case 'L': case 'T': case 'd': case 'l': case 't': goto yy392; case 'E': case 'e': goto yy393; case 'I': case 'i': goto yy394; default: goto yy358; } yy366: yych = *++p; if (yych <= 'R') { if (yych <= 'N') { if (yych == 'I') goto yy395; goto yy358; } else { if (yych <= 'O') goto yy396; if (yych <= 'Q') goto yy358; goto yy397; } } else { if (yych <= 'n') { if (yych == 'i') goto yy395; goto yy358; } else { if (yych <= 'o') goto yy396; if (yych == 'r') goto yy397; goto yy358; } } yy367: yych = *++p; if (yych <= 'S') { if (yych <= 'D') { if (yych <= '0') goto yy358; if (yych <= '6') goto yy392; goto yy358; } else { if (yych <= 'E') goto yy398; if (yych == 'R') goto yy392; goto yy358; } } else { if (yych <= 'q') { if (yych <= 'T') goto yy399; if (yych == 'e') goto yy398; goto yy358; } else { if (yych <= 'r') goto yy392; if (yych == 't') goto yy399; goto yy358; } } yy368: yych = *++p; if (yych == 'F') goto yy400; if (yych == 'f') goto yy400; goto yy358; yy369: yych = *++p; if (yych <= 'I') { if (yych == 'E') goto yy401; if (yych <= 'H') goto yy358; goto yy402; } else { if (yych <= 'e') { if (yych <= 'd') goto yy358; goto yy401; } else { if (yych == 'i') goto yy402; goto yy358; } } yy370: yych = *++p; if (yych <= 'E') { if (yych == 'A') goto yy403; if (yych <= 'D') goto yy358; goto yy404; } else { if (yych <= 'a') { if (yych <= '`') goto yy358; goto yy403; } else { if (yych == 'e') goto yy404; goto yy358; } } yy371: yych = *++p; if (yych <= 'O') { if (yych == 'A') goto yy405; if (yych <= 'N') goto yy358; goto yy406; } else { if (yych <= 'a') { if (yych <= '`') goto yy358; goto yy405; } else { if (yych == 'o') goto yy406; goto yy358; } } yy372: yych = *++p; if (yych <= 'P') { if (yych == 'L') goto yy392; if (yych <= 'O') goto yy358; goto yy407; } else { if (yych <= 'l') { if (yych <= 'k') goto yy358; goto yy392; } else { if (yych == 'p') goto yy407; goto yy358; } } yy373: yych = *++p; if (yych <= '>') { if (yych <= ' ') { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; if (yych <= 0x1F) goto yy358; goto yy408; } else { if (yych == '/') goto yy410; if (yych <= '=') goto yy358; goto yy408; } } else { if (yych <= 'R') { if (yych == 'A') goto yy411; if (yych <= 'Q') goto yy358; goto yy412; } else { if (yych <= 'a') { if (yych <= '`') goto yy358; goto yy411; } else { if (yych == 'r') goto yy412; goto yy358; } } } yy374: yych = *++p; switch (yych) { case 'C': case 'c': goto yy413; case 'E': case 'e': goto yy414; case 'O': case 'o': goto yy415; case 'T': case 't': goto yy416; case 'U': case 'u': goto yy417; default: goto yy358; } yy375: yych = *++p; switch (yych) { case 'A': case 'a': goto yy418; case 'B': case 'b': goto yy419; case 'D': case 'd': goto yy392; case 'F': case 'f': goto yy420; case 'H': case 'h': goto yy421; case 'I': case 'i': goto yy422; case 'R': case 'r': goto yy423; default: goto yy358; } yy376: yych = *++p; if (yych == 'L') goto yy392; if (yych == 'l') goto yy392; goto yy358; yy377: yych = *++p; if (yych == '-') goto yy424; goto yy358; yy378: ++p; { return 4; } yy380: yych = *++p; if (yych == 'C') goto yy426; if (yych == 'c') goto yy426; goto yy358; yy381: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= '@') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'A') goto yy411; if (yych == 'a') goto yy411; goto yy358; } } yy382: yych = *++p; if (yych <= 'U') { if (yych <= 'N') { if (yych == 'E') goto yy414; goto yy358; } else { if (yych <= 'O') goto yy415; if (yych <= 'T') goto yy358; goto yy417; } } else { if (yych <= 'n') { if (yych == 'e') goto yy414; goto yy358; } else { if (yych <= 'o') goto yy415; if (yych == 'u') goto yy417; goto yy358; } } yy383: yych = *++p; if (yych == 'D') goto yy427; if (yych == 'd') goto yy427; goto yy358; yy384: yych = *++p; if (yych == 'T') goto yy428; if (yych == 't') goto yy428; goto yy358; yy385: yych = *++p; if (yych == 'I') goto yy429; if (yych == 'i') goto yy429; goto yy358; yy386: yych = *++p; if (yych == 'S') goto yy430; if (yych == 's') goto yy430; goto yy358; yy387: yych = *++p; if (yych == 'O') goto yy431; if (yych == 'o') goto yy431; goto yy358; yy388: yych = *++p; if (yych == 'D') goto yy432; if (yych == 'd') goto yy432; goto yy358; yy389: yych = *++p; if (yych == 'P') goto yy433; if (yych == 'p') goto yy433; goto yy358; yy390: yych = *++p; if (yych == 'N') goto yy434; if (yych == 'n') goto yy434; goto yy358; yy391: yych = *++p; if (yych == 'L') goto yy435; if (yych == 'l') goto yy435; goto yy358; yy392: yych = *++p; if (yych <= ' ') { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; if (yych <= 0x1F) goto yy358; goto yy408; } else { if (yych <= '/') { if (yych <= '.') goto yy358; goto yy410; } else { if (yych == '>') goto yy408; goto yy358; } } yy393: yych = *++p; if (yych == 'T') goto yy436; if (yych == 't') goto yy436; goto yy358; yy394: yych = *++p; if (yych <= 'V') { if (yych <= 'Q') { if (yych == 'A') goto yy437; goto yy358; } else { if (yych <= 'R') goto yy392; if (yych <= 'U') goto yy358; goto yy392; } } else { if (yych <= 'q') { if (yych == 'a') goto yy437; goto yy358; } else { if (yych <= 'r') goto yy392; if (yych == 'v') goto yy392; goto yy358; } } yy395: yych = *++p; if (yych <= 'G') { if (yych == 'E') goto yy438; if (yych <= 'F') goto yy358; goto yy439; } else { if (yych <= 'e') { if (yych <= 'd') goto yy358; goto yy438; } else { if (yych == 'g') goto yy439; goto yy358; } } yy396: yych = *++p; if (yych <= 'R') { if (yych == 'O') goto yy434; if (yych <= 'Q') goto yy358; goto yy440; } else { if (yych <= 'o') { if (yych <= 'n') goto yy358; goto yy434; } else { if (yych == 'r') goto yy440; goto yy358; } } yy397: yych = *++p; if (yych == 'A') goto yy441; if (yych == 'a') goto yy441; goto yy358; yy398: yych = *++p; if (yych == 'A') goto yy442; if (yych == 'a') goto yy442; goto yy358; yy399: yych = *++p; if (yych == 'M') goto yy376; if (yych == 'm') goto yy376; goto yy358; yy400: yych = *++p; if (yych == 'R') goto yy443; if (yych == 'r') goto yy443; goto yy358; yy401: yych = *++p; if (yych == 'G') goto yy444; if (yych == 'g') goto yy444; goto yy358; yy402: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= 'M') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'N') goto yy445; if (yych == 'n') goto yy445; goto yy358; } } yy403: yych = *++p; if (yych == 'I') goto yy446; if (yych == 'i') goto yy446; goto yy358; yy404: yych = *++p; if (yych == 'N') goto yy447; if (yych == 'n') goto yy447; goto yy358; yy405: yych = *++p; if (yych == 'V') goto yy392; if (yych == 'v') goto yy392; goto yy358; yy406: yych = *++p; if (yych == 'F') goto yy448; if (yych == 'f') goto yy448; goto yy358; yy407: yych = *++p; if (yych == 'T') goto yy449; if (yych == 't') goto yy449; goto yy358; yy408: ++p; { return 6; } yy410: yych = *++p; if (yych == '>') goto yy408; goto yy358; yy411: yych = *++p; if (yych == 'R') goto yy450; if (yych == 'r') goto yy450; goto yy358; yy412: yych = *++p; if (yych == 'E') goto yy451; if (yych == 'e') goto yy451; goto yy358; yy413: yych = *++p; if (yych == 'R') goto yy452; if (yych == 'r') goto yy452; goto yy358; yy414: yych = *++p; if (yych == 'C') goto yy433; if (yych == 'c') goto yy433; goto yy358; yy415: yych = *++p; if (yych == 'U') goto yy453; if (yych == 'u') goto yy453; goto yy358; yy416: yych = *++p; if (yych == 'Y') goto yy454; if (yych == 'y') goto yy454; goto yy358; yy417: yych = *++p; if (yych == 'M') goto yy455; if (yych == 'm') goto yy455; goto yy358; yy418: yych = *++p; if (yych == 'B') goto yy456; if (yych == 'b') goto yy456; goto yy358; yy419: yych = *++p; if (yych == 'O') goto yy388; if (yych == 'o') goto yy388; goto yy358; yy420: yych = *++p; if (yych == 'O') goto yy457; if (yych == 'o') goto yy457; goto yy358; yy421: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= 'D') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'E') goto yy458; if (yych == 'e') goto yy458; goto yy358; } } yy422: yych = *++p; if (yych == 'T') goto yy456; if (yych == 't') goto yy456; goto yy358; yy423: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= '@') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'A') goto yy459; if (yych == 'a') goto yy459; goto yy358; } } yy424: ++p; { return 2; } yy426: yych = *++p; if (yych == 'D') goto yy460; if (yych == 'd') goto yy460; goto yy358; yy427: yych = *++p; if (yych == 'R') goto yy461; if (yych == 'r') goto yy461; goto yy358; yy428: yych = *++p; if (yych == 'I') goto yy462; if (yych == 'i') goto yy462; goto yy358; yy429: yych = *++p; if (yych == 'D') goto yy463; if (yych == 'd') goto yy463; goto yy358; yy430: yych = *++p; if (yych == 'E') goto yy464; if (yych == 'e') goto yy464; goto yy358; yy431: yych = *++p; if (yych == 'C') goto yy465; if (yych == 'c') goto yy465; goto yy358; yy432: yych = *++p; if (yych == 'Y') goto yy392; if (yych == 'y') goto yy392; goto yy358; yy433: yych = *++p; if (yych == 'T') goto yy466; if (yych == 't') goto yy466; goto yy358; yy434: yych = *++p; if (yych == 'T') goto yy467; if (yych == 't') goto yy467; goto yy358; yy435: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= 'F') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'G') goto yy468; if (yych == 'g') goto yy468; goto yy358; } } yy436: yych = *++p; if (yych == 'A') goto yy469; if (yych == 'a') goto yy469; goto yy358; yy437: yych = *++p; if (yych == 'L') goto yy470; if (yych == 'l') goto yy470; goto yy358; yy438: yych = *++p; if (yych == 'L') goto yy471; if (yych == 'l') goto yy471; goto yy358; yy439: yych = *++p; if (yych <= 'U') { if (yych == 'C') goto yy472; if (yych <= 'T') goto yy358; goto yy473; } else { if (yych <= 'c') { if (yych <= 'b') goto yy358; goto yy472; } else { if (yych == 'u') goto yy473; goto yy358; } } yy440: yych = *++p; if (yych == 'M') goto yy392; if (yych == 'm') goto yy392; goto yy358; yy441: yych = *++p; if (yych == 'M') goto yy474; if (yych == 'm') goto yy474; goto yy358; yy442: yych = *++p; if (yych == 'D') goto yy475; if (yych == 'd') goto yy475; goto yy358; yy443: yych = *++p; if (yych == 'A') goto yy476; if (yych == 'a') goto yy476; goto yy358; yy444: yych = *++p; if (yych == 'E') goto yy477; if (yych == 'e') goto yy477; goto yy358; yy445: yych = *++p; if (yych == 'K') goto yy392; if (yych == 'k') goto yy392; goto yy358; yy446: yych = *++p; if (yych == 'N') goto yy392; if (yych == 'n') goto yy392; goto yy358; yy447: yych = *++p; if (yych == 'U') goto yy478; if (yych == 'u') goto yy478; goto yy358; yy448: yych = *++p; if (yych == 'R') goto yy479; if (yych == 'r') goto yy479; goto yy358; yy449: yych = *++p; if (yych <= 'I') { if (yych == 'G') goto yy468; if (yych <= 'H') goto yy358; goto yy480; } else { if (yych <= 'g') { if (yych <= 'f') goto yy358; goto yy468; } else { if (yych == 'i') goto yy480; goto yy358; } } yy450: yych = *++p; if (yych == 'A') goto yy440; if (yych == 'a') goto yy440; goto yy358; yy451: yych = *++p; if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy481; goto yy358; } else { if (yych <= ' ') goto yy481; if (yych == '>') goto yy481; goto yy358; } yy452: yych = *++p; if (yych == 'I') goto yy483; if (yych == 'i') goto yy483; goto yy358; yy453: yych = *++p; if (yych == 'R') goto yy484; if (yych == 'r') goto yy484; goto yy358; yy454: yych = *++p; if (yych == 'L') goto yy412; if (yych == 'l') goto yy412; goto yy358; yy455: yych = *++p; if (yych == 'M') goto yy485; if (yych == 'm') goto yy485; goto yy358; yy456: yych = *++p; if (yych == 'L') goto yy463; if (yych == 'l') goto yy463; goto yy358; yy457: yych = *++p; if (yych == 'O') goto yy486; if (yych == 'o') goto yy486; goto yy358; yy458: yych = *++p; if (yych == 'A') goto yy487; if (yych == 'a') goto yy487; goto yy358; yy459: yych = *++p; if (yych == 'C') goto yy445; if (yych == 'c') goto yy445; goto yy358; yy460: yych = *++p; if (yych == 'A') goto yy488; if (yych == 'a') goto yy488; goto yy358; yy461: yych = *++p; if (yych == 'E') goto yy489; if (yych == 'e') goto yy489; goto yy358; yy462: yych = *++p; if (yych == 'C') goto yy456; if (yych == 'c') goto yy456; goto yy358; yy463: yych = *++p; if (yych == 'E') goto yy392; if (yych == 'e') goto yy392; goto yy358; yy464: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= 'E') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'F') goto yy490; if (yych == 'f') goto yy490; goto yy358; } } yy465: yych = *++p; if (yych == 'K') goto yy491; if (yych == 'k') goto yy491; goto yy358; yy466: yych = *++p; if (yych == 'I') goto yy480; if (yych == 'i') goto yy480; goto yy358; yy467: yych = *++p; if (yych == 'E') goto yy492; if (yych == 'e') goto yy492; goto yy358; yy468: yych = *++p; if (yych == 'R') goto yy493; if (yych == 'r') goto yy493; goto yy358; yy469: yych = *++p; if (yych == 'I') goto yy494; if (yych == 'i') goto yy494; goto yy358; yy470: yych = *++p; if (yych == 'O') goto yy495; if (yych == 'o') goto yy495; goto yy358; yy471: yych = *++p; if (yych == 'D') goto yy496; if (yych == 'd') goto yy496; goto yy358; yy472: yych = *++p; if (yych == 'A') goto yy389; if (yych == 'a') goto yy389; goto yy358; yy473: yych = *++p; if (yych == 'R') goto yy463; if (yych == 'r') goto yy463; goto yy358; yy474: yych = *++p; if (yych == 'E') goto yy497; if (yych == 'e') goto yy497; goto yy358; yy475: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= 'D') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'E') goto yy492; if (yych == 'e') goto yy492; goto yy358; } } yy476: yych = *++p; if (yych == 'M') goto yy463; if (yych == 'm') goto yy463; goto yy358; yy477: yych = *++p; if (yych == 'N') goto yy487; if (yych == 'n') goto yy487; goto yy358; yy478: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= 'H') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'I') goto yy498; if (yych == 'i') goto yy498; goto yy358; } } yy479: yych = *++p; if (yych == 'A') goto yy499; if (yych == 'a') goto yy499; goto yy358; yy480: yych = *++p; if (yych == 'O') goto yy446; if (yych == 'o') goto yy446; goto yy358; yy481: ++p; { return 1; } yy483: yych = *++p; if (yych == 'P') goto yy500; if (yych == 'p') goto yy500; goto yy358; yy484: yych = *++p; if (yych == 'C') goto yy463; if (yych == 'c') goto yy463; goto yy358; yy485: yych = *++p; if (yych == 'A') goto yy501; if (yych == 'a') goto yy501; goto yy358; yy486: yych = *++p; if (yych == 'T') goto yy392; if (yych == 't') goto yy392; goto yy358; yy487: yych = *++p; if (yych == 'D') goto yy392; if (yych == 'd') goto yy392; goto yy358; yy488: yych = *++p; if (yych == 'T') goto yy502; if (yych == 't') goto yy502; goto yy358; yy489: yych = *++p; if (yych == 'S') goto yy503; if (yych == 's') goto yy503; goto yy358; yy490: yych = *++p; if (yych == 'O') goto yy504; if (yych == 'o') goto yy504; goto yy358; yy491: yych = *++p; if (yych == 'Q') goto yy505; if (yych == 'q') goto yy505; goto yy358; yy492: yych = *++p; if (yych == 'R') goto yy392; if (yych == 'r') goto yy392; goto yy358; yy493: yych = *++p; if (yych == 'O') goto yy506; if (yych == 'o') goto yy506; goto yy358; yy494: yych = *++p; if (yych == 'L') goto yy503; if (yych == 'l') goto yy503; goto yy358; yy495: yych = *++p; if (yych == 'G') goto yy392; if (yych == 'g') goto yy392; goto yy358; yy496: yych = *++p; if (yych == 'S') goto yy507; if (yych == 's') goto yy507; goto yy358; yy497: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy358; if (yych <= '\r') goto yy408; goto yy358; } else { if (yych <= ' ') goto yy408; if (yych <= '.') goto yy358; goto yy410; } } else { if (yych <= 'R') { if (yych == '>') goto yy408; goto yy358; } else { if (yych <= 'S') goto yy507; if (yych == 's') goto yy507; goto yy358; } } yy498: yych = *++p; if (yych == 'T') goto yy508; if (yych == 't') goto yy508; goto yy358; yy499: yych = *++p; if (yych == 'M') goto yy509; if (yych == 'm') goto yy509; goto yy358; yy500: yych = *++p; if (yych == 'T') goto yy451; if (yych == 't') goto yy451; goto yy358; yy501: yych = *++p; if (yych == 'R') goto yy432; if (yych == 'r') goto yy432; goto yy358; yy502: yych = *++p; if (yych == 'A') goto yy510; if (yych == 'a') goto yy510; goto yy358; yy503: yych = *++p; if (yych == 'S') goto yy392; if (yych == 's') goto yy392; goto yy358; yy504: yych = *++p; if (yych == 'N') goto yy486; if (yych == 'n') goto yy486; goto yy358; yy505: yych = *++p; if (yych == 'U') goto yy511; if (yych == 'u') goto yy511; goto yy358; yy506: yych = *++p; if (yych == 'U') goto yy512; if (yych == 'u') goto yy512; goto yy358; yy507: yych = *++p; if (yych == 'E') goto yy486; if (yych == 'e') goto yy486; goto yy358; yy508: yych = *++p; if (yych == 'E') goto yy440; if (yych == 'e') goto yy440; goto yy358; yy509: yych = *++p; if (yych == 'E') goto yy503; if (yych == 'e') goto yy503; goto yy358; yy510: yych = *++p; if (yych == '[') goto yy513; goto yy358; yy511: yych = *++p; if (yych == 'O') goto yy515; if (yych == 'o') goto yy515; goto yy358; yy512: yych = *++p; if (yych == 'P') goto yy392; if (yych == 'p') goto yy392; goto yy358; yy513: ++p; { return 5; } yy515: yych = *++p; if (yych == 'T') goto yy463; if (yych == 't') goto yy463; goto yy358; } } // Try to match an HTML block tag start line of type 7, returning // 7 if successful, 0 if not. bufsize_t _scan_html_block_start_7(const unsigned char *p) { const unsigned char *marker = NULL; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 224, 224, 224, 224, 224, 224, 224, 224, 198, 210, 194, 198, 194, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 224, 198, 224, 128, 224, 224, 224, 224, 64, 224, 224, 224, 224, 224, 233, 232, 224, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 232, 224, 192, 192, 192, 224, 224, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 224, 224, 224, 224, 232, 192, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 233, 224, 224, 224, 224, 224, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych == '<') goto yy520; ++p; yy519: { return 0; } yy520: yyaccept = 0; yych = *(marker = ++p); if (yych <= '@') { if (yych != '/') goto yy519; } else { if (yych <= 'Z') goto yy523; if (yych <= '`') goto yy519; if (yych <= 'z') goto yy523; goto yy519; } yych = *++p; if (yych <= '@') goto yy522; if (yych <= 'Z') goto yy525; if (yych <= '`') goto yy522; if (yych <= 'z') goto yy525; yy522: p = marker; if (yyaccept == 0) { goto yy519; } else { goto yy538; } yy523: yych = *++p; if (yybm[0+yych] & 2) { goto yy527; } if (yych <= '=') { if (yych <= '.') { if (yych == '-') goto yy523; goto yy522; } else { if (yych <= '/') goto yy529; if (yych <= '9') goto yy523; goto yy522; } } else { if (yych <= 'Z') { if (yych <= '>') goto yy530; if (yych <= '@') goto yy522; goto yy523; } else { if (yych <= '`') goto yy522; if (yych <= 'z') goto yy523; goto yy522; } } yy525: yych = *++p; if (yych <= '/') { if (yych <= 0x1F) { if (yych <= 0x08) goto yy522; if (yych <= '\r') goto yy532; goto yy522; } else { if (yych <= ' ') goto yy532; if (yych == '-') goto yy525; goto yy522; } } else { if (yych <= '@') { if (yych <= '9') goto yy525; if (yych == '>') goto yy530; goto yy522; } else { if (yych <= 'Z') goto yy525; if (yych <= '`') goto yy522; if (yych <= 'z') goto yy525; goto yy522; } } yy527: yych = *++p; if (yybm[0+yych] & 2) { goto yy527; } if (yych <= '>') { if (yych <= '9') { if (yych != '/') goto yy522; } else { if (yych <= ':') goto yy534; if (yych <= '=') goto yy522; goto yy530; } } else { if (yych <= '^') { if (yych <= '@') goto yy522; if (yych <= 'Z') goto yy534; goto yy522; } else { if (yych == '`') goto yy522; if (yych <= 'z') goto yy534; goto yy522; } } yy529: yych = *++p; if (yych != '>') goto yy522; yy530: yych = *++p; if (yybm[0+yych] & 4) { goto yy530; } if (yych <= 0x08) goto yy522; if (yych <= '\n') goto yy536; if (yych <= '\v') goto yy522; if (yych <= '\r') goto yy539; goto yy522; yy532: yych = *++p; if (yych <= 0x1F) { if (yych <= 0x08) goto yy522; if (yych <= '\r') goto yy532; goto yy522; } else { if (yych <= ' ') goto yy532; if (yych == '>') goto yy530; goto yy522; } yy534: yych = *++p; if (yybm[0+yych] & 8) { goto yy534; } if (yych <= ',') { if (yych <= '\r') { if (yych <= 0x08) goto yy522; goto yy540; } else { if (yych == ' ') goto yy540; goto yy522; } } else { if (yych <= '<') { if (yych <= '/') goto yy529; goto yy522; } else { if (yych <= '=') goto yy542; if (yych <= '>') goto yy530; goto yy522; } } yy536: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 4) { goto yy530; } if (yych <= 0x08) goto yy538; if (yych <= '\n') goto yy536; if (yych <= '\v') goto yy538; if (yych <= '\r') goto yy539; yy538: { return 7; } yy539: ++p; goto yy538; yy540: yych = *++p; if (yych <= '<') { if (yych <= ' ') { if (yych <= 0x08) goto yy522; if (yych <= '\r') goto yy540; if (yych <= 0x1F) goto yy522; goto yy540; } else { if (yych <= '/') { if (yych <= '.') goto yy522; goto yy529; } else { if (yych == ':') goto yy534; goto yy522; } } } else { if (yych <= 'Z') { if (yych <= '=') goto yy542; if (yych <= '>') goto yy530; if (yych <= '@') goto yy522; goto yy534; } else { if (yych <= '_') { if (yych <= '^') goto yy522; goto yy534; } else { if (yych <= '`') goto yy522; if (yych <= 'z') goto yy534; goto yy522; } } } yy542: yych = *++p; if (yybm[0+yych] & 32) { goto yy544; } if (yych <= 0xE0) { if (yych <= '"') { if (yych <= 0x00) goto yy522; if (yych <= ' ') goto yy542; goto yy546; } else { if (yych <= '\'') goto yy548; if (yych <= 0xC1) goto yy522; if (yych <= 0xDF) goto yy550; goto yy551; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy553; goto yy552; } else { if (yych <= 0xF0) goto yy554; if (yych <= 0xF3) goto yy555; if (yych <= 0xF4) goto yy556; goto yy522; } } yy544: yych = *++p; if (yybm[0+yych] & 32) { goto yy544; } if (yych <= 0xE0) { if (yych <= '=') { if (yych <= 0x00) goto yy522; if (yych <= ' ') goto yy527; goto yy522; } else { if (yych <= '>') goto yy530; if (yych <= 0xC1) goto yy522; if (yych <= 0xDF) goto yy550; goto yy551; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy553; goto yy552; } else { if (yych <= 0xF0) goto yy554; if (yych <= 0xF3) goto yy555; if (yych <= 0xF4) goto yy556; goto yy522; } } yy546: yych = *++p; if (yybm[0+yych] & 64) { goto yy546; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy522; if (yych <= '"') goto yy557; goto yy522; } else { if (yych <= 0xDF) goto yy558; if (yych <= 0xE0) goto yy559; goto yy560; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy561; if (yych <= 0xEF) goto yy560; goto yy562; } else { if (yych <= 0xF3) goto yy563; if (yych <= 0xF4) goto yy564; goto yy522; } } yy548: yych = *++p; if (yybm[0+yych] & 128) { goto yy548; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy522; if (yych <= '\'') goto yy557; goto yy522; } else { if (yych <= 0xDF) goto yy565; if (yych <= 0xE0) goto yy566; goto yy567; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy568; if (yych <= 0xEF) goto yy567; goto yy569; } else { if (yych <= 0xF3) goto yy570; if (yych <= 0xF4) goto yy571; goto yy522; } } yy550: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy544; goto yy522; yy551: yych = *++p; if (yych <= 0x9F) goto yy522; if (yych <= 0xBF) goto yy550; goto yy522; yy552: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy550; goto yy522; yy553: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0x9F) goto yy550; goto yy522; yy554: yych = *++p; if (yych <= 0x8F) goto yy522; if (yych <= 0xBF) goto yy552; goto yy522; yy555: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy552; goto yy522; yy556: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0x8F) goto yy552; goto yy522; yy557: yych = *++p; if (yybm[0+yych] & 2) { goto yy527; } if (yych == '/') goto yy529; if (yych == '>') goto yy530; goto yy522; yy558: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy546; goto yy522; yy559: yych = *++p; if (yych <= 0x9F) goto yy522; if (yych <= 0xBF) goto yy558; goto yy522; yy560: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy558; goto yy522; yy561: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0x9F) goto yy558; goto yy522; yy562: yych = *++p; if (yych <= 0x8F) goto yy522; if (yych <= 0xBF) goto yy560; goto yy522; yy563: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy560; goto yy522; yy564: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0x8F) goto yy560; goto yy522; yy565: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy548; goto yy522; yy566: yych = *++p; if (yych <= 0x9F) goto yy522; if (yych <= 0xBF) goto yy565; goto yy522; yy567: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy565; goto yy522; yy568: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0x9F) goto yy565; goto yy522; yy569: yych = *++p; if (yych <= 0x8F) goto yy522; if (yych <= 0xBF) goto yy567; goto yy522; yy570: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0xBF) goto yy567; goto yy522; yy571: yych = *++p; if (yych <= 0x7F) goto yy522; if (yych <= 0x8F) goto yy567; goto yy522; } } // Try to match an HTML block end line of type 1 bufsize_t _scan_html_block_end_1(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 128, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= 0xDF) { if (yych <= ';') { if (yych <= 0x00) goto yy574; if (yych != '\n') goto yy576; } else { if (yych <= '<') goto yy577; if (yych <= 0x7F) goto yy576; if (yych >= 0xC2) goto yy578; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy579; if (yych == 0xED) goto yy581; goto yy580; } else { if (yych <= 0xF0) goto yy582; if (yych <= 0xF3) goto yy583; if (yych <= 0xF4) goto yy584; } } yy574: ++p; yy575: { return 0; } yy576: yyaccept = 0; yych = *(marker = ++p); if (yych <= '\n') { if (yych <= 0x00) goto yy575; if (yych <= '\t') goto yy586; goto yy575; } else { if (yych <= 0x7F) goto yy586; if (yych <= 0xC1) goto yy575; if (yych <= 0xF4) goto yy586; goto yy575; } yy577: yyaccept = 0; yych = *(marker = ++p); if (yych <= '.') { if (yych <= 0x00) goto yy575; if (yych == '\n') goto yy575; goto yy586; } else { if (yych <= 0x7F) { if (yych <= '/') goto yy597; goto yy586; } else { if (yych <= 0xC1) goto yy575; if (yych <= 0xF4) goto yy586; goto yy575; } } yy578: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy575; if (yych <= 0xBF) goto yy585; goto yy575; yy579: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x9F) goto yy575; if (yych <= 0xBF) goto yy590; goto yy575; yy580: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy575; if (yych <= 0xBF) goto yy590; goto yy575; yy581: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy575; if (yych <= 0x9F) goto yy590; goto yy575; yy582: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x8F) goto yy575; if (yych <= 0xBF) goto yy592; goto yy575; yy583: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy575; if (yych <= 0xBF) goto yy592; goto yy575; yy584: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy575; if (yych <= 0x8F) goto yy592; goto yy575; yy585: yych = *++p; yy586: if (yybm[0+yych] & 64) { goto yy585; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy587; if (yych <= '<') goto yy588; } else { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; goto yy592; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy593; if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; } } yy587: p = marker; if (yyaccept == 0) { goto yy575; } else { goto yy607; } yy588: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xDF) { if (yych <= '.') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= '/') goto yy597; if (yych <= 0x7F) goto yy585; if (yych <= 0xC1) goto yy587; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy591; if (yych == 0xED) goto yy593; goto yy592; } else { if (yych <= 0xF0) goto yy594; if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } yy590: yych = *++p; if (yych <= 0x7F) goto yy587; if (yych <= 0xBF) goto yy585; goto yy587; yy591: yych = *++p; if (yych <= 0x9F) goto yy587; if (yych <= 0xBF) goto yy590; goto yy587; yy592: yych = *++p; if (yych <= 0x7F) goto yy587; if (yych <= 0xBF) goto yy590; goto yy587; yy593: yych = *++p; if (yych <= 0x7F) goto yy587; if (yych <= 0x9F) goto yy590; goto yy587; yy594: yych = *++p; if (yych <= 0x8F) goto yy587; if (yych <= 0xBF) goto yy592; goto yy587; yy595: yych = *++p; if (yych <= 0x7F) goto yy587; if (yych <= 0xBF) goto yy592; goto yy587; yy596: yych = *++p; if (yych <= 0x7F) goto yy587; if (yych <= 0x8F) goto yy592; goto yy587; yy597: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 's') { if (yych <= 'P') { if (yych <= '\t') { if (yych <= 0x00) goto yy587; goto yy585; } else { if (yych <= '\n') goto yy587; if (yych <= 'O') goto yy585; } } else { if (yych <= 'o') { if (yych == 'S') goto yy599; goto yy585; } else { if (yych <= 'p') goto yy598; if (yych <= 'r') goto yy585; goto yy599; } } } else { if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x7F) goto yy585; goto yy587; } else { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; goto yy592; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy593; if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy598: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'Q') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 'q') { if (yych <= 'R') goto yy600; goto yy585; } else { if (yych <= 'r') goto yy600; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy599: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 't') { if (yych <= 'C') { if (yych <= '\t') { if (yych <= 0x00) goto yy587; goto yy585; } else { if (yych <= '\n') goto yy587; if (yych <= 'B') goto yy585; goto yy601; } } else { if (yych <= 'b') { if (yych == 'T') goto yy602; goto yy585; } else { if (yych <= 'c') goto yy601; if (yych <= 's') goto yy585; goto yy602; } } } else { if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x7F) goto yy585; goto yy587; } else { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; goto yy592; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy593; if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy600: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'D') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 'd') { if (yych <= 'E') goto yy603; goto yy585; } else { if (yych <= 'e') goto yy603; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy601: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'Q') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 'q') { if (yych <= 'R') goto yy604; goto yy585; } else { if (yych <= 'r') goto yy604; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy602: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'X') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 'x') { if (yych <= 'Y') goto yy605; goto yy585; } else { if (yych <= 'y') goto yy605; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy603: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xDF) { if (yych <= '=') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= '>') goto yy606; if (yych <= 0x7F) goto yy585; if (yych <= 0xC1) goto yy587; goto yy590; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy591; if (yych == 0xED) goto yy593; goto yy592; } else { if (yych <= 0xF0) goto yy594; if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } yy604: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'H') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 'h') { if (yych <= 'I') goto yy608; goto yy585; } else { if (yych <= 'i') goto yy608; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy605: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'K') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 'k') { if (yych <= 'L') goto yy600; goto yy585; } else { if (yych <= 'l') goto yy600; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy606: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 64) { goto yy585; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy607; if (yych <= '<') goto yy588; } else { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; goto yy592; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy593; if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; } } yy607: { return (bufsize_t)(p - start); } yy608: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'O') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 'o') { if (yych >= 'Q') goto yy585; } else { if (yych <= 'p') goto yy609; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } yy609: yych = *++p; if (yybm[0+yych] & 128) { goto yy588; } if (yych <= 0xC1) { if (yych <= 'S') { if (yych <= 0x00) goto yy587; if (yych == '\n') goto yy587; goto yy585; } else { if (yych <= 's') { if (yych <= 'T') goto yy603; goto yy585; } else { if (yych <= 't') goto yy603; if (yych <= 0x7F) goto yy585; goto yy587; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy590; if (yych <= 0xE0) goto yy591; if (yych <= 0xEC) goto yy592; goto yy593; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy592; goto yy594; } else { if (yych <= 0xF3) goto yy595; if (yych <= 0xF4) goto yy596; goto yy587; } } } } } // Try to match an HTML block end line of type 2 bufsize_t _scan_html_block_end_2(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 128, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= 0xDF) { if (yych <= ',') { if (yych <= 0x00) goto yy612; if (yych != '\n') goto yy614; } else { if (yych <= '-') goto yy615; if (yych <= 0x7F) goto yy614; if (yych >= 0xC2) goto yy616; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy617; if (yych == 0xED) goto yy619; goto yy618; } else { if (yych <= 0xF0) goto yy620; if (yych <= 0xF3) goto yy621; if (yych <= 0xF4) goto yy622; } } yy612: ++p; yy613: { return 0; } yy614: yyaccept = 0; yych = *(marker = ++p); if (yych <= '\n') { if (yych <= 0x00) goto yy613; if (yych <= '\t') goto yy624; goto yy613; } else { if (yych <= 0x7F) goto yy624; if (yych <= 0xC1) goto yy613; if (yych <= 0xF4) goto yy624; goto yy613; } yy615: yyaccept = 0; yych = *(marker = ++p); if (yybm[0+yych] & 128) { goto yy634; } if (yych <= '\n') { if (yych <= 0x00) goto yy613; if (yych <= '\t') goto yy624; goto yy613; } else { if (yych <= 0x7F) goto yy624; if (yych <= 0xC1) goto yy613; if (yych <= 0xF4) goto yy624; goto yy613; } yy616: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy613; if (yych <= 0xBF) goto yy623; goto yy613; yy617: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x9F) goto yy613; if (yych <= 0xBF) goto yy627; goto yy613; yy618: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy613; if (yych <= 0xBF) goto yy627; goto yy613; yy619: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy613; if (yych <= 0x9F) goto yy627; goto yy613; yy620: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x8F) goto yy613; if (yych <= 0xBF) goto yy629; goto yy613; yy621: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy613; if (yych <= 0xBF) goto yy629; goto yy613; yy622: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy613; if (yych <= 0x8F) goto yy629; goto yy613; yy623: yych = *++p; yy624: if (yybm[0+yych] & 64) { goto yy623; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy625; if (yych <= '-') goto yy626; } else { if (yych <= 0xDF) goto yy627; if (yych <= 0xE0) goto yy628; goto yy629; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy630; if (yych <= 0xEF) goto yy629; goto yy631; } else { if (yych <= 0xF3) goto yy632; if (yych <= 0xF4) goto yy633; } } yy625: p = marker; if (yyaccept == 0) { goto yy613; } else { goto yy637; } yy626: yych = *++p; if (yybm[0+yych] & 64) { goto yy623; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy625; if (yych <= '-') goto yy634; goto yy625; } else { if (yych <= 0xDF) goto yy627; if (yych <= 0xE0) goto yy628; goto yy629; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy630; if (yych <= 0xEF) goto yy629; goto yy631; } else { if (yych <= 0xF3) goto yy632; if (yych <= 0xF4) goto yy633; goto yy625; } } yy627: yych = *++p; if (yych <= 0x7F) goto yy625; if (yych <= 0xBF) goto yy623; goto yy625; yy628: yych = *++p; if (yych <= 0x9F) goto yy625; if (yych <= 0xBF) goto yy627; goto yy625; yy629: yych = *++p; if (yych <= 0x7F) goto yy625; if (yych <= 0xBF) goto yy627; goto yy625; yy630: yych = *++p; if (yych <= 0x7F) goto yy625; if (yych <= 0x9F) goto yy627; goto yy625; yy631: yych = *++p; if (yych <= 0x8F) goto yy625; if (yych <= 0xBF) goto yy629; goto yy625; yy632: yych = *++p; if (yych <= 0x7F) goto yy625; if (yych <= 0xBF) goto yy629; goto yy625; yy633: yych = *++p; if (yych <= 0x7F) goto yy625; if (yych <= 0x8F) goto yy629; goto yy625; yy634: yych = *++p; if (yybm[0+yych] & 128) { goto yy634; } if (yych <= 0xDF) { if (yych <= '=') { if (yych <= 0x00) goto yy625; if (yych == '\n') goto yy625; goto yy623; } else { if (yych <= '>') goto yy636; if (yych <= 0x7F) goto yy623; if (yych <= 0xC1) goto yy625; goto yy627; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy628; if (yych == 0xED) goto yy630; goto yy629; } else { if (yych <= 0xF0) goto yy631; if (yych <= 0xF3) goto yy632; if (yych <= 0xF4) goto yy633; goto yy625; } } yy636: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 64) { goto yy623; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy637; if (yych <= '-') goto yy626; } else { if (yych <= 0xDF) goto yy627; if (yych <= 0xE0) goto yy628; goto yy629; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy630; if (yych <= 0xEF) goto yy629; goto yy631; } else { if (yych <= 0xF3) goto yy632; if (yych <= 0xF4) goto yy633; } } yy637: { return (bufsize_t)(p - start); } } } // Try to match an HTML block end line of type 3 bufsize_t _scan_html_block_end_3(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 128, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= 0xDF) { if (yych <= '>') { if (yych <= 0x00) goto yy640; if (yych != '\n') goto yy642; } else { if (yych <= '?') goto yy643; if (yych <= 0x7F) goto yy642; if (yych >= 0xC2) goto yy644; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy645; if (yych == 0xED) goto yy647; goto yy646; } else { if (yych <= 0xF0) goto yy648; if (yych <= 0xF3) goto yy649; if (yych <= 0xF4) goto yy650; } } yy640: ++p; yy641: { return 0; } yy642: yyaccept = 0; yych = *(marker = ++p); if (yych <= '\n') { if (yych <= 0x00) goto yy641; if (yych <= '\t') goto yy652; goto yy641; } else { if (yych <= 0x7F) goto yy652; if (yych <= 0xC1) goto yy641; if (yych <= 0xF4) goto yy652; goto yy641; } yy643: yyaccept = 0; yych = *(marker = ++p); if (yych <= '=') { if (yych <= 0x00) goto yy641; if (yych == '\n') goto yy641; goto yy652; } else { if (yych <= 0x7F) { if (yych <= '>') goto yy663; goto yy652; } else { if (yych <= 0xC1) goto yy641; if (yych <= 0xF4) goto yy652; goto yy641; } } yy644: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy641; if (yych <= 0xBF) goto yy651; goto yy641; yy645: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x9F) goto yy641; if (yych <= 0xBF) goto yy656; goto yy641; yy646: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy641; if (yych <= 0xBF) goto yy656; goto yy641; yy647: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy641; if (yych <= 0x9F) goto yy656; goto yy641; yy648: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x8F) goto yy641; if (yych <= 0xBF) goto yy658; goto yy641; yy649: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy641; if (yych <= 0xBF) goto yy658; goto yy641; yy650: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy641; if (yych <= 0x8F) goto yy658; goto yy641; yy651: yych = *++p; yy652: if (yybm[0+yych] & 64) { goto yy651; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy653; if (yych <= '?') goto yy654; } else { if (yych <= 0xDF) goto yy656; if (yych <= 0xE0) goto yy657; goto yy658; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy659; if (yych <= 0xEF) goto yy658; goto yy660; } else { if (yych <= 0xF3) goto yy661; if (yych <= 0xF4) goto yy662; } } yy653: p = marker; if (yyaccept == 0) { goto yy641; } else { goto yy664; } yy654: yych = *++p; if (yybm[0+yych] & 128) { goto yy654; } if (yych <= 0xDF) { if (yych <= '=') { if (yych <= 0x00) goto yy653; if (yych == '\n') goto yy653; goto yy651; } else { if (yych <= '>') goto yy663; if (yych <= 0x7F) goto yy651; if (yych <= 0xC1) goto yy653; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy657; if (yych == 0xED) goto yy659; goto yy658; } else { if (yych <= 0xF0) goto yy660; if (yych <= 0xF3) goto yy661; if (yych <= 0xF4) goto yy662; goto yy653; } } yy656: yych = *++p; if (yych <= 0x7F) goto yy653; if (yych <= 0xBF) goto yy651; goto yy653; yy657: yych = *++p; if (yych <= 0x9F) goto yy653; if (yych <= 0xBF) goto yy656; goto yy653; yy658: yych = *++p; if (yych <= 0x7F) goto yy653; if (yych <= 0xBF) goto yy656; goto yy653; yy659: yych = *++p; if (yych <= 0x7F) goto yy653; if (yych <= 0x9F) goto yy656; goto yy653; yy660: yych = *++p; if (yych <= 0x8F) goto yy653; if (yych <= 0xBF) goto yy658; goto yy653; yy661: yych = *++p; if (yych <= 0x7F) goto yy653; if (yych <= 0xBF) goto yy658; goto yy653; yy662: yych = *++p; if (yych <= 0x7F) goto yy653; if (yych <= 0x8F) goto yy658; goto yy653; yy663: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 64) { goto yy651; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy664; if (yych <= '?') goto yy654; } else { if (yych <= 0xDF) goto yy656; if (yych <= 0xE0) goto yy657; goto yy658; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy659; if (yych <= 0xEF) goto yy658; goto yy660; } else { if (yych <= 0xF3) goto yy661; if (yych <= 0xF4) goto yy662; } } yy664: { return (bufsize_t)(p - start); } } } // Try to match an HTML block end line of type 4 bufsize_t _scan_html_block_end_4(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 64, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yybm[0+yych] & 64) { goto yy670; } if (yych <= 0xE0) { if (yych <= '\n') { if (yych <= 0x00) goto yy667; if (yych <= '\t') goto yy669; } else { if (yych <= 0x7F) goto yy669; if (yych <= 0xC1) goto yy667; if (yych <= 0xDF) goto yy673; goto yy674; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy676; goto yy675; } else { if (yych <= 0xF0) goto yy677; if (yych <= 0xF3) goto yy678; if (yych <= 0xF4) goto yy679; } } yy667: ++p; yy668: { return 0; } yy669: yyaccept = 0; yych = *(marker = ++p); if (yych <= '\n') { if (yych <= 0x00) goto yy668; if (yych <= '\t') goto yy681; goto yy668; } else { if (yych <= 0x7F) goto yy681; if (yych <= 0xC1) goto yy668; if (yych <= 0xF4) goto yy681; goto yy668; } yy670: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 128) { goto yy680; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy672; if (yych <= '>') goto yy670; } else { if (yych <= 0xDF) goto yy683; if (yych <= 0xE0) goto yy684; goto yy685; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy686; if (yych <= 0xEF) goto yy685; goto yy687; } else { if (yych <= 0xF3) goto yy688; if (yych <= 0xF4) goto yy689; } } yy672: { return (bufsize_t)(p - start); } yy673: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy668; if (yych <= 0xBF) goto yy680; goto yy668; yy674: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x9F) goto yy668; if (yych <= 0xBF) goto yy683; goto yy668; yy675: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy668; if (yych <= 0xBF) goto yy683; goto yy668; yy676: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy668; if (yych <= 0x9F) goto yy683; goto yy668; yy677: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x8F) goto yy668; if (yych <= 0xBF) goto yy685; goto yy668; yy678: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy668; if (yych <= 0xBF) goto yy685; goto yy668; yy679: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy668; if (yych <= 0x8F) goto yy685; goto yy668; yy680: yych = *++p; yy681: if (yybm[0+yych] & 128) { goto yy680; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy682; if (yych <= '>') goto yy670; } else { if (yych <= 0xDF) goto yy683; if (yych <= 0xE0) goto yy684; goto yy685; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy686; if (yych <= 0xEF) goto yy685; goto yy687; } else { if (yych <= 0xF3) goto yy688; if (yych <= 0xF4) goto yy689; } } yy682: p = marker; if (yyaccept == 0) { goto yy668; } else { goto yy672; } yy683: yych = *++p; if (yych <= 0x7F) goto yy682; if (yych <= 0xBF) goto yy680; goto yy682; yy684: yych = *++p; if (yych <= 0x9F) goto yy682; if (yych <= 0xBF) goto yy683; goto yy682; yy685: yych = *++p; if (yych <= 0x7F) goto yy682; if (yych <= 0xBF) goto yy683; goto yy682; yy686: yych = *++p; if (yych <= 0x7F) goto yy682; if (yych <= 0x9F) goto yy683; goto yy682; yy687: yych = *++p; if (yych <= 0x8F) goto yy682; if (yych <= 0xBF) goto yy685; goto yy682; yy688: yych = *++p; if (yych <= 0x7F) goto yy682; if (yych <= 0xBF) goto yy685; goto yy682; yy689: yych = *++p; if (yych <= 0x7F) goto yy682; if (yych <= 0x8F) goto yy685; goto yy682; } } // Try to match an HTML block end line of type 5 bufsize_t _scan_html_block_end_5(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 128, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= 0xDF) { if (yych <= '\\') { if (yych <= 0x00) goto yy692; if (yych != '\n') goto yy694; } else { if (yych <= ']') goto yy695; if (yych <= 0x7F) goto yy694; if (yych >= 0xC2) goto yy696; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy697; if (yych == 0xED) goto yy699; goto yy698; } else { if (yych <= 0xF0) goto yy700; if (yych <= 0xF3) goto yy701; if (yych <= 0xF4) goto yy702; } } yy692: ++p; yy693: { return 0; } yy694: yyaccept = 0; yych = *(marker = ++p); if (yych <= '\n') { if (yych <= 0x00) goto yy693; if (yych <= '\t') goto yy704; goto yy693; } else { if (yych <= 0x7F) goto yy704; if (yych <= 0xC1) goto yy693; if (yych <= 0xF4) goto yy704; goto yy693; } yy695: yyaccept = 0; yych = *(marker = ++p); if (yybm[0+yych] & 128) { goto yy714; } if (yych <= '\n') { if (yych <= 0x00) goto yy693; if (yych <= '\t') goto yy704; goto yy693; } else { if (yych <= 0x7F) goto yy704; if (yych <= 0xC1) goto yy693; if (yych <= 0xF4) goto yy704; goto yy693; } yy696: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy693; if (yych <= 0xBF) goto yy703; goto yy693; yy697: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x9F) goto yy693; if (yych <= 0xBF) goto yy707; goto yy693; yy698: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy693; if (yych <= 0xBF) goto yy707; goto yy693; yy699: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy693; if (yych <= 0x9F) goto yy707; goto yy693; yy700: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x8F) goto yy693; if (yych <= 0xBF) goto yy709; goto yy693; yy701: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy693; if (yych <= 0xBF) goto yy709; goto yy693; yy702: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x7F) goto yy693; if (yych <= 0x8F) goto yy709; goto yy693; yy703: yych = *++p; yy704: if (yybm[0+yych] & 64) { goto yy703; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy705; if (yych <= ']') goto yy706; } else { if (yych <= 0xDF) goto yy707; if (yych <= 0xE0) goto yy708; goto yy709; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy710; if (yych <= 0xEF) goto yy709; goto yy711; } else { if (yych <= 0xF3) goto yy712; if (yych <= 0xF4) goto yy713; } } yy705: p = marker; if (yyaccept == 0) { goto yy693; } else { goto yy717; } yy706: yych = *++p; if (yybm[0+yych] & 64) { goto yy703; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy705; if (yych <= ']') goto yy714; goto yy705; } else { if (yych <= 0xDF) goto yy707; if (yych <= 0xE0) goto yy708; goto yy709; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy710; if (yych <= 0xEF) goto yy709; goto yy711; } else { if (yych <= 0xF3) goto yy712; if (yych <= 0xF4) goto yy713; goto yy705; } } yy707: yych = *++p; if (yych <= 0x7F) goto yy705; if (yych <= 0xBF) goto yy703; goto yy705; yy708: yych = *++p; if (yych <= 0x9F) goto yy705; if (yych <= 0xBF) goto yy707; goto yy705; yy709: yych = *++p; if (yych <= 0x7F) goto yy705; if (yych <= 0xBF) goto yy707; goto yy705; yy710: yych = *++p; if (yych <= 0x7F) goto yy705; if (yych <= 0x9F) goto yy707; goto yy705; yy711: yych = *++p; if (yych <= 0x8F) goto yy705; if (yych <= 0xBF) goto yy709; goto yy705; yy712: yych = *++p; if (yych <= 0x7F) goto yy705; if (yych <= 0xBF) goto yy709; goto yy705; yy713: yych = *++p; if (yych <= 0x7F) goto yy705; if (yych <= 0x8F) goto yy709; goto yy705; yy714: yych = *++p; if (yybm[0+yych] & 128) { goto yy714; } if (yych <= 0xDF) { if (yych <= '=') { if (yych <= 0x00) goto yy705; if (yych == '\n') goto yy705; goto yy703; } else { if (yych <= '>') goto yy716; if (yych <= 0x7F) goto yy703; if (yych <= 0xC1) goto yy705; goto yy707; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy708; if (yych == 0xED) goto yy710; goto yy709; } else { if (yych <= 0xF0) goto yy711; if (yych <= 0xF3) goto yy712; if (yych <= 0xF4) goto yy713; goto yy705; } } yy716: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 64) { goto yy703; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\n') goto yy717; if (yych <= ']') goto yy706; } else { if (yych <= 0xDF) goto yy707; if (yych <= 0xE0) goto yy708; goto yy709; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy710; if (yych <= 0xEF) goto yy709; goto yy711; } else { if (yych <= 0xF3) goto yy712; if (yych <= 0xF4) goto yy713; } } yy717: { return (bufsize_t)(p - start); } } } // Try to match a link title (in single quotes, in double quotes, or // in parentheses), returning number of chars matched. Allow one // level of internal nesting (quotes within quotes). bufsize_t _scan_link_title(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 192, 208, 208, 208, 208, 144, 208, 80, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 32, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 208, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= '&') { if (yych == '"') goto yy722; } else { if (yych <= '\'') goto yy723; if (yych <= '(') goto yy724; } ++p; yy721: { return 0; } yy722: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x00) goto yy721; if (yych <= 0x7F) goto yy726; if (yych <= 0xC1) goto yy721; if (yych <= 0xF4) goto yy726; goto yy721; yy723: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x00) goto yy721; if (yych <= 0x7F) goto yy740; if (yych <= 0xC1) goto yy721; if (yych <= 0xF4) goto yy740; goto yy721; yy724: yyaccept = 0; yych = *(marker = ++p); if (yych <= 0x00) goto yy721; if (yych <= 0x7F) goto yy753; if (yych <= 0xC1) goto yy721; if (yych <= 0xF4) goto yy753; goto yy721; yy725: yych = *++p; yy726: if (yybm[0+yych] & 16) { goto yy725; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy727; if (yych <= '"') goto yy728; goto yy730; } else { if (yych <= 0xC1) goto yy727; if (yych <= 0xDF) goto yy732; goto yy733; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy735; goto yy734; } else { if (yych <= 0xF0) goto yy736; if (yych <= 0xF3) goto yy737; if (yych <= 0xF4) goto yy738; } } yy727: p = marker; if (yyaccept <= 1) { if (yyaccept == 0) { goto yy721; } else { goto yy729; } } else { if (yyaccept == 2) { goto yy742; } else { goto yy755; } } yy728: ++p; yy729: { return (bufsize_t)(p - start); } yy730: yych = *++p; if (yybm[0+yych] & 16) { goto yy725; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy727; if (yych <= '"') goto yy765; goto yy730; } else { if (yych <= 0xC1) goto yy727; if (yych >= 0xE0) goto yy733; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy735; goto yy734; } else { if (yych <= 0xF0) goto yy736; if (yych <= 0xF3) goto yy737; if (yych <= 0xF4) goto yy738; goto yy727; } } yy732: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy725; goto yy727; yy733: yych = *++p; if (yych <= 0x9F) goto yy727; if (yych <= 0xBF) goto yy732; goto yy727; yy734: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy732; goto yy727; yy735: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0x9F) goto yy732; goto yy727; yy736: yych = *++p; if (yych <= 0x8F) goto yy727; if (yych <= 0xBF) goto yy734; goto yy727; yy737: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy734; goto yy727; yy738: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0x8F) goto yy734; goto yy727; yy739: yych = *++p; yy740: if (yybm[0+yych] & 64) { goto yy739; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy727; if (yych >= '(') goto yy743; } else { if (yych <= 0xC1) goto yy727; if (yych <= 0xDF) goto yy745; goto yy746; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy748; goto yy747; } else { if (yych <= 0xF0) goto yy749; if (yych <= 0xF3) goto yy750; if (yych <= 0xF4) goto yy751; goto yy727; } } yy741: ++p; yy742: { return (bufsize_t)(p - start); } yy743: yych = *++p; if (yybm[0+yych] & 64) { goto yy739; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy727; if (yych <= '\'') goto yy766; goto yy743; } else { if (yych <= 0xC1) goto yy727; if (yych >= 0xE0) goto yy746; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy748; goto yy747; } else { if (yych <= 0xF0) goto yy749; if (yych <= 0xF3) goto yy750; if (yych <= 0xF4) goto yy751; goto yy727; } } yy745: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy739; goto yy727; yy746: yych = *++p; if (yych <= 0x9F) goto yy727; if (yych <= 0xBF) goto yy745; goto yy727; yy747: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy745; goto yy727; yy748: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0x9F) goto yy745; goto yy727; yy749: yych = *++p; if (yych <= 0x8F) goto yy727; if (yych <= 0xBF) goto yy747; goto yy727; yy750: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy747; goto yy727; yy751: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0x8F) goto yy747; goto yy727; yy752: yych = *++p; yy753: if (yybm[0+yych] & 128) { goto yy752; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy727; if (yych >= '*') goto yy756; } else { if (yych <= 0xC1) goto yy727; if (yych <= 0xDF) goto yy758; goto yy759; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy761; goto yy760; } else { if (yych <= 0xF0) goto yy762; if (yych <= 0xF3) goto yy763; if (yych <= 0xF4) goto yy764; goto yy727; } } yy754: ++p; yy755: { return (bufsize_t)(p - start); } yy756: yych = *++p; if (yybm[0+yych] & 128) { goto yy752; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy727; if (yych <= ')') goto yy767; goto yy756; } else { if (yych <= 0xC1) goto yy727; if (yych >= 0xE0) goto yy759; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy761; goto yy760; } else { if (yych <= 0xF0) goto yy762; if (yych <= 0xF3) goto yy763; if (yych <= 0xF4) goto yy764; goto yy727; } } yy758: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy752; goto yy727; yy759: yych = *++p; if (yych <= 0x9F) goto yy727; if (yych <= 0xBF) goto yy758; goto yy727; yy760: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy758; goto yy727; yy761: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0x9F) goto yy758; goto yy727; yy762: yych = *++p; if (yych <= 0x8F) goto yy727; if (yych <= 0xBF) goto yy760; goto yy727; yy763: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0xBF) goto yy760; goto yy727; yy764: yych = *++p; if (yych <= 0x7F) goto yy727; if (yych <= 0x8F) goto yy760; goto yy727; yy765: yyaccept = 1; yych = *(marker = ++p); if (yybm[0+yych] & 16) { goto yy725; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy729; if (yych <= '"') goto yy728; goto yy730; } else { if (yych <= 0xC1) goto yy729; if (yych <= 0xDF) goto yy732; goto yy733; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy735; goto yy734; } else { if (yych <= 0xF0) goto yy736; if (yych <= 0xF3) goto yy737; if (yych <= 0xF4) goto yy738; goto yy729; } } yy766: yyaccept = 2; yych = *(marker = ++p); if (yybm[0+yych] & 64) { goto yy739; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy742; if (yych <= '\'') goto yy741; goto yy743; } else { if (yych <= 0xC1) goto yy742; if (yych <= 0xDF) goto yy745; goto yy746; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy748; goto yy747; } else { if (yych <= 0xF0) goto yy749; if (yych <= 0xF3) goto yy750; if (yych <= 0xF4) goto yy751; goto yy742; } } yy767: yyaccept = 3; yych = *(marker = ++p); if (yybm[0+yych] & 128) { goto yy752; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= 0x00) goto yy755; if (yych <= ')') goto yy754; goto yy756; } else { if (yych <= 0xC1) goto yy755; if (yych <= 0xDF) goto yy758; goto yy759; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy761; goto yy760; } else { if (yych <= 0xF0) goto yy762; if (yych <= 0xF3) goto yy763; if (yych <= 0xF4) goto yy764; goto yy755; } } } } // Match space characters, including newlines. bufsize_t _scan_spacechars(const unsigned char *p) { const unsigned char *start = p; \ { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 128, 128, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yybm[0+yych] & 128) { goto yy772; } ++p; { return 0; } yy772: yych = *++p; if (yybm[0+yych] & 128) { goto yy772; } { return (bufsize_t)(p - start); } } } // Match ATX heading start. bufsize_t _scan_atx_heading_start(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych == '#') goto yy779; ++p; yy778: { return 0; } yy779: yych = *(marker = ++p); if (yybm[0+yych] & 128) { goto yy780; } if (yych <= '\f') { if (yych <= 0x08) goto yy778; if (yych <= '\n') goto yy783; goto yy778; } else { if (yych <= '\r') goto yy783; if (yych == '#') goto yy784; goto yy778; } yy780: yych = *++p; if (yybm[0+yych] & 128) { goto yy780; } yy782: { return (bufsize_t)(p - start); } yy783: ++p; goto yy782; yy784: yych = *++p; if (yybm[0+yych] & 128) { goto yy780; } if (yych <= '\f') { if (yych <= 0x08) goto yy785; if (yych <= '\n') goto yy783; } else { if (yych <= '\r') goto yy783; if (yych == '#') goto yy786; } yy785: p = marker; goto yy778; yy786: yych = *++p; if (yybm[0+yych] & 128) { goto yy780; } if (yych <= '\f') { if (yych <= 0x08) goto yy785; if (yych <= '\n') goto yy783; goto yy785; } else { if (yych <= '\r') goto yy783; if (yych != '#') goto yy785; } yych = *++p; if (yybm[0+yych] & 128) { goto yy780; } if (yych <= '\f') { if (yych <= 0x08) goto yy785; if (yych <= '\n') goto yy783; goto yy785; } else { if (yych <= '\r') goto yy783; if (yych != '#') goto yy785; } yych = *++p; if (yybm[0+yych] & 128) { goto yy780; } if (yych <= '\f') { if (yych <= 0x08) goto yy785; if (yych <= '\n') goto yy783; goto yy785; } else { if (yych <= '\r') goto yy783; if (yych != '#') goto yy785; } yych = *++p; if (yybm[0+yych] & 128) { goto yy780; } if (yych <= 0x08) goto yy785; if (yych <= '\n') goto yy783; if (yych == '\r') goto yy783; goto yy785; } } // Match setext heading line. Return 1 for level-1 heading, // 2 for level-2, 0 for no match. bufsize_t _scan_setext_heading_line(const unsigned char *p) { const unsigned char *marker = NULL; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 32, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 32, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych == '-') goto yy794; if (yych == '=') goto yy795; ++p; yy793: { return 0; } yy794: yych = *(marker = ++p); if (yybm[0+yych] & 64) { goto yy801; } if (yych <= '\f') { if (yych <= 0x08) goto yy793; if (yych <= '\n') goto yy797; goto yy793; } else { if (yych <= '\r') goto yy797; if (yych == ' ') goto yy797; goto yy793; } yy795: yych = *(marker = ++p); if (yybm[0+yych] & 128) { goto yy807; } if (yych <= '\f') { if (yych <= 0x08) goto yy793; if (yych <= '\n') goto yy804; goto yy793; } else { if (yych <= '\r') goto yy804; if (yych == ' ') goto yy804; goto yy793; } yy796: yych = *++p; yy797: if (yybm[0+yych] & 32) { goto yy796; } if (yych <= 0x08) goto yy798; if (yych <= '\n') goto yy799; if (yych == '\r') goto yy799; yy798: p = marker; goto yy793; yy799: ++p; { return 2; } yy801: yych = *++p; if (yybm[0+yych] & 32) { goto yy796; } if (yych <= '\f') { if (yych <= 0x08) goto yy798; if (yych <= '\n') goto yy799; goto yy798; } else { if (yych <= '\r') goto yy799; if (yych == '-') goto yy801; goto yy798; } yy803: yych = *++p; yy804: if (yych <= '\f') { if (yych <= 0x08) goto yy798; if (yych <= '\t') goto yy803; if (yych >= '\v') goto yy798; } else { if (yych <= '\r') goto yy805; if (yych == ' ') goto yy803; goto yy798; } yy805: ++p; { return 1; } yy807: yych = *++p; if (yybm[0+yych] & 128) { goto yy807; } if (yych <= '\f') { if (yych <= 0x08) goto yy798; if (yych <= '\t') goto yy803; if (yych <= '\n') goto yy805; goto yy798; } else { if (yych <= '\r') goto yy805; if (yych == ' ') goto yy803; goto yy798; } } } // Scan a thematic break line: "...three or more hyphens, asterisks, // or underscores on a line by themselves. If you wish, you may use // spaces between the hyphens or asterisks." bufsize_t _scan_thematic_break(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 240, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 240, 0, 0, 0, 0, 0, 0, 0, 0, 0, 32, 0, 0, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych <= ',') { if (yych == '*') goto yy813; } else { if (yych <= '-') goto yy814; if (yych == '_') goto yy815; } ++p; yy812: { return 0; } yy813: yych = *(marker = ++p); if (yybm[0+yych] & 16) { goto yy816; } if (yych == '*') goto yy819; goto yy812; yy814: yych = *(marker = ++p); if (yych <= 0x1F) { if (yych == '\t') goto yy821; goto yy812; } else { if (yych <= ' ') goto yy821; if (yych == '-') goto yy823; goto yy812; } yy815: yych = *(marker = ++p); if (yych <= 0x1F) { if (yych == '\t') goto yy825; goto yy812; } else { if (yych <= ' ') goto yy825; if (yych == '_') goto yy827; goto yy812; } yy816: yych = *++p; if (yybm[0+yych] & 16) { goto yy816; } if (yych == '*') goto yy819; yy818: p = marker; goto yy812; yy819: yych = *++p; if (yych <= 0x1F) { if (yych == '\t') goto yy819; goto yy818; } else { if (yych <= ' ') goto yy819; if (yych == '*') goto yy829; goto yy818; } yy821: yych = *++p; if (yych <= 0x1F) { if (yych == '\t') goto yy821; goto yy818; } else { if (yych <= ' ') goto yy821; if (yych != '-') goto yy818; } yy823: yych = *++p; if (yych <= 0x1F) { if (yych == '\t') goto yy823; goto yy818; } else { if (yych <= ' ') goto yy823; if (yych == '-') goto yy831; goto yy818; } yy825: yych = *++p; if (yych <= 0x1F) { if (yych == '\t') goto yy825; goto yy818; } else { if (yych <= ' ') goto yy825; if (yych != '_') goto yy818; } yy827: yych = *++p; if (yych <= 0x1F) { if (yych == '\t') goto yy827; goto yy818; } else { if (yych <= ' ') goto yy827; if (yych == '_') goto yy833; goto yy818; } yy829: yych = *++p; if (yybm[0+yych] & 32) { goto yy829; } if (yych <= 0x08) goto yy818; if (yych <= '\n') goto yy835; if (yych == '\r') goto yy835; goto yy818; yy831: yych = *++p; if (yybm[0+yych] & 64) { goto yy831; } if (yych <= 0x08) goto yy818; if (yych <= '\n') goto yy837; if (yych == '\r') goto yy837; goto yy818; yy833: yych = *++p; if (yybm[0+yych] & 128) { goto yy833; } if (yych <= 0x08) goto yy818; if (yych <= '\n') goto yy839; if (yych == '\r') goto yy839; goto yy818; yy835: ++p; { return (bufsize_t)(p - start); } yy837: ++p; { return (bufsize_t)(p - start); } yy839: ++p; { return (bufsize_t)(p - start); } } } // Scan an opening code fence. bufsize_t _scan_open_code_fence(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 192, 192, 192, 192, 192, 192, 192, 192, 192, 0, 192, 192, 0, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 144, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 192, 224, 192, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych == '`') goto yy845; if (yych == '~') goto yy846; ++p; yy844: { return 0; } yy845: yych = *(marker = ++p); if (yych == '`') goto yy847; goto yy844; yy846: yych = *(marker = ++p); if (yych == '~') goto yy849; goto yy844; yy847: yych = *++p; if (yybm[0+yych] & 16) { goto yy850; } yy848: p = marker; goto yy844; yy849: yych = *++p; if (yybm[0+yych] & 32) { goto yy852; } goto yy848; yy850: yych = *++p; if (yybm[0+yych] & 16) { goto yy850; } if (yych <= 0xDF) { if (yych <= '\f') { if (yych <= 0x00) goto yy848; if (yych == '\n') { marker = p; goto yy856; } marker = p; goto yy854; } else { if (yych <= '\r') { marker = p; goto yy856; } if (yych <= 0x7F) { marker = p; goto yy854; } if (yych <= 0xC1) goto yy848; marker = p; goto yy858; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) { marker = p; goto yy859; } if (yych == 0xED) { marker = p; goto yy861; } marker = p; goto yy860; } else { if (yych <= 0xF0) { marker = p; goto yy862; } if (yych <= 0xF3) { marker = p; goto yy863; } if (yych <= 0xF4) { marker = p; goto yy864; } goto yy848; } } yy852: yych = *++p; if (yybm[0+yych] & 32) { goto yy852; } if (yych <= 0xDF) { if (yych <= '\f') { if (yych <= 0x00) goto yy848; if (yych == '\n') { marker = p; goto yy867; } marker = p; goto yy865; } else { if (yych <= '\r') { marker = p; goto yy867; } if (yych <= 0x7F) { marker = p; goto yy865; } if (yych <= 0xC1) goto yy848; marker = p; goto yy869; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) { marker = p; goto yy870; } if (yych == 0xED) { marker = p; goto yy872; } marker = p; goto yy871; } else { if (yych <= 0xF0) { marker = p; goto yy873; } if (yych <= 0xF3) { marker = p; goto yy874; } if (yych <= 0xF4) { marker = p; goto yy875; } goto yy848; } } yy854: yych = *++p; if (yybm[0+yych] & 64) { goto yy854; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy848; if (yych >= 0x0E) goto yy848; } else { if (yych <= 0xDF) goto yy858; if (yych <= 0xE0) goto yy859; goto yy860; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy861; if (yych <= 0xEF) goto yy860; goto yy862; } else { if (yych <= 0xF3) goto yy863; if (yych <= 0xF4) goto yy864; goto yy848; } } yy856: ++p; p = marker; { return (bufsize_t)(p - start); } yy858: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0xBF) goto yy854; goto yy848; yy859: yych = *++p; if (yych <= 0x9F) goto yy848; if (yych <= 0xBF) goto yy858; goto yy848; yy860: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0xBF) goto yy858; goto yy848; yy861: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0x9F) goto yy858; goto yy848; yy862: yych = *++p; if (yych <= 0x8F) goto yy848; if (yych <= 0xBF) goto yy860; goto yy848; yy863: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0xBF) goto yy860; goto yy848; yy864: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0x8F) goto yy860; goto yy848; yy865: yych = *++p; if (yybm[0+yych] & 128) { goto yy865; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= 0x00) goto yy848; if (yych >= 0x0E) goto yy848; } else { if (yych <= 0xDF) goto yy869; if (yych <= 0xE0) goto yy870; goto yy871; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy872; if (yych <= 0xEF) goto yy871; goto yy873; } else { if (yych <= 0xF3) goto yy874; if (yych <= 0xF4) goto yy875; goto yy848; } } yy867: ++p; p = marker; { return (bufsize_t)(p - start); } yy869: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0xBF) goto yy865; goto yy848; yy870: yych = *++p; if (yych <= 0x9F) goto yy848; if (yych <= 0xBF) goto yy869; goto yy848; yy871: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0xBF) goto yy869; goto yy848; yy872: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0x9F) goto yy869; goto yy848; yy873: yych = *++p; if (yych <= 0x8F) goto yy848; if (yych <= 0xBF) goto yy871; goto yy848; yy874: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0xBF) goto yy871; goto yy848; yy875: yych = *++p; if (yych <= 0x7F) goto yy848; if (yych <= 0x8F) goto yy871; goto yy848; } } // Scan a closing code fence with length at least len. bufsize_t _scan_close_code_fence(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 32, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych == '`') goto yy880; if (yych == '~') goto yy881; ++p; yy879: { return 0; } yy880: yych = *(marker = ++p); if (yych == '`') goto yy882; goto yy879; yy881: yych = *(marker = ++p); if (yych == '~') goto yy884; goto yy879; yy882: yych = *++p; if (yybm[0+yych] & 32) { goto yy885; } yy883: p = marker; goto yy879; yy884: yych = *++p; if (yybm[0+yych] & 64) { goto yy887; } goto yy883; yy885: yych = *++p; if (yybm[0+yych] & 32) { goto yy885; } if (yych <= '\f') { if (yych <= 0x08) goto yy883; if (yych <= '\t') { marker = p; goto yy889; } if (yych <= '\n') { marker = p; goto yy891; } goto yy883; } else { if (yych <= '\r') { marker = p; goto yy891; } if (yych == ' ') { marker = p; goto yy889; } goto yy883; } yy887: yych = *++p; if (yybm[0+yych] & 64) { goto yy887; } if (yych <= '\f') { if (yych <= 0x08) goto yy883; if (yych <= '\t') { marker = p; goto yy893; } if (yych <= '\n') { marker = p; goto yy895; } goto yy883; } else { if (yych <= '\r') { marker = p; goto yy895; } if (yych == ' ') { marker = p; goto yy893; } goto yy883; } yy889: yych = *++p; if (yybm[0+yych] & 128) { goto yy889; } if (yych <= 0x08) goto yy883; if (yych <= '\n') goto yy891; if (yych != '\r') goto yy883; yy891: ++p; p = marker; { return (bufsize_t)(p - start); } yy893: yych = *++p; if (yych <= '\f') { if (yych <= 0x08) goto yy883; if (yych <= '\t') goto yy893; if (yych >= '\v') goto yy883; } else { if (yych <= '\r') goto yy895; if (yych == ' ') goto yy893; goto yy883; } yy895: ++p; p = marker; { return (bufsize_t)(p - start); } } } // Scans an entity. // Returns number of chars matched. bufsize_t _scan_entity(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; yych = *p; if (yych == '&') goto yy901; ++p; yy900: { return 0; } yy901: yych = *(marker = ++p); if (yych <= '@') { if (yych != '#') goto yy900; } else { if (yych <= 'Z') goto yy904; if (yych <= '`') goto yy900; if (yych <= 'z') goto yy904; goto yy900; } yych = *++p; if (yych <= 'W') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy905; } else { if (yych <= 'X') goto yy906; if (yych == 'x') goto yy906; } yy903: p = marker; goto yy900; yy904: yych = *++p; if (yych <= '@') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy907; goto yy903; } else { if (yych <= 'Z') goto yy907; if (yych <= '`') goto yy903; if (yych <= 'z') goto yy907; goto yy903; } yy905: yych = *++p; if (yych <= '/') goto yy903; if (yych <= '9') goto yy908; if (yych == ';') goto yy909; goto yy903; yy906: yych = *++p; if (yych <= '@') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy911; goto yy903; } else { if (yych <= 'F') goto yy911; if (yych <= '`') goto yy903; if (yych <= 'f') goto yy911; goto yy903; } yy907: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy912; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; goto yy912; } else { if (yych <= '`') goto yy903; if (yych <= 'z') goto yy912; goto yy903; } } yy908: yych = *++p; if (yych <= '/') goto yy903; if (yych <= '9') goto yy913; if (yych != ';') goto yy903; yy909: ++p; { return (bufsize_t)(p - start); } yy911: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy914; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'F') { if (yych <= '@') goto yy903; goto yy914; } else { if (yych <= '`') goto yy903; if (yych <= 'f') goto yy914; goto yy903; } } yy912: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy915; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; goto yy915; } else { if (yych <= '`') goto yy903; if (yych <= 'z') goto yy915; goto yy903; } } yy913: yych = *++p; if (yych <= '/') goto yy903; if (yych <= '9') goto yy916; if (yych == ';') goto yy909; goto yy903; yy914: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy917; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'F') { if (yych <= '@') goto yy903; goto yy917; } else { if (yych <= '`') goto yy903; if (yych <= 'f') goto yy917; goto yy903; } } yy915: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy918; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; goto yy918; } else { if (yych <= '`') goto yy903; if (yych <= 'z') goto yy918; goto yy903; } } yy916: yych = *++p; if (yych <= '/') goto yy903; if (yych <= '9') goto yy919; if (yych == ';') goto yy909; goto yy903; yy917: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy920; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'F') { if (yych <= '@') goto yy903; goto yy920; } else { if (yych <= '`') goto yy903; if (yych <= 'f') goto yy920; goto yy903; } } yy918: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy921; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; goto yy921; } else { if (yych <= '`') goto yy903; if (yych <= 'z') goto yy921; goto yy903; } } yy919: yych = *++p; if (yych <= '/') goto yy903; if (yych <= '9') goto yy922; if (yych == ';') goto yy909; goto yy903; yy920: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy923; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'F') { if (yych <= '@') goto yy903; goto yy923; } else { if (yych <= '`') goto yy903; if (yych <= 'f') goto yy923; goto yy903; } } yy921: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy924; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; goto yy924; } else { if (yych <= '`') goto yy903; if (yych <= 'z') goto yy924; goto yy903; } } yy922: yych = *++p; if (yych <= '/') goto yy903; if (yych <= '9') goto yy925; if (yych == ';') goto yy909; goto yy903; yy923: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy925; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'F') { if (yych <= '@') goto yy903; goto yy925; } else { if (yych <= '`') goto yy903; if (yych <= 'f') goto yy925; goto yy903; } } yy924: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy926; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; goto yy926; } else { if (yych <= '`') goto yy903; if (yych <= 'z') goto yy926; goto yy903; } } yy925: yych = *++p; if (yych == ';') goto yy909; goto yy903; yy926: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy927; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy927: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy928; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy928: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy929; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy929: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy930; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy930: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy931; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy931: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy932; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy932: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy933; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy933: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy934; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy934: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy935; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy935: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy936; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy936: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy937; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy937: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy938; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy938: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy939; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy939: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy940; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy940: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy941; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy941: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy942; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy942: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy943; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy943: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy944; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy944: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy945; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy945: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy946; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy946: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy947; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy947: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy948; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy948: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy949; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; } else { if (yych <= '`') goto yy903; if (yych >= '{') goto yy903; } } yy949: yych = *++p; if (yych <= ';') { if (yych <= '/') goto yy903; if (yych <= '9') goto yy925; if (yych <= ':') goto yy903; goto yy909; } else { if (yych <= 'Z') { if (yych <= '@') goto yy903; goto yy925; } else { if (yych <= '`') goto yy903; if (yych <= 'z') goto yy925; goto yy903; } } } } // Returns positive value if a URL begins in a way that is potentially // dangerous, with javascript:, vbscript:, file:, or data:, otherwise 0. bufsize_t _scan_dangerous_url(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; yych = *p; if (yych <= 'V') { if (yych <= 'F') { if (yych == 'D') goto yy954; if (yych >= 'F') goto yy955; } else { if (yych == 'J') goto yy956; if (yych >= 'V') goto yy957; } } else { if (yych <= 'f') { if (yych == 'd') goto yy954; if (yych >= 'f') goto yy955; } else { if (yych <= 'j') { if (yych >= 'j') goto yy956; } else { if (yych == 'v') goto yy957; } } } ++p; yy953: { return 0; } yy954: yyaccept = 0; yych = *(marker = ++p); if (yych == 'A') goto yy958; if (yych == 'a') goto yy958; goto yy953; yy955: yyaccept = 0; yych = *(marker = ++p); if (yych == 'I') goto yy960; if (yych == 'i') goto yy960; goto yy953; yy956: yyaccept = 0; yych = *(marker = ++p); if (yych == 'A') goto yy961; if (yych == 'a') goto yy961; goto yy953; yy957: yyaccept = 0; yych = *(marker = ++p); if (yych == 'B') goto yy962; if (yych == 'b') goto yy962; goto yy953; yy958: yych = *++p; if (yych == 'T') goto yy963; if (yych == 't') goto yy963; yy959: p = marker; if (yyaccept == 0) { goto yy953; } else { goto yy971; } yy960: yych = *++p; if (yych == 'L') goto yy964; if (yych == 'l') goto yy964; goto yy959; yy961: yych = *++p; if (yych == 'V') goto yy965; if (yych == 'v') goto yy965; goto yy959; yy962: yych = *++p; if (yych == 'S') goto yy966; if (yych == 's') goto yy966; goto yy959; yy963: yych = *++p; if (yych == 'A') goto yy967; if (yych == 'a') goto yy967; goto yy959; yy964: yych = *++p; if (yych == 'E') goto yy968; if (yych == 'e') goto yy968; goto yy959; yy965: yych = *++p; if (yych == 'A') goto yy962; if (yych == 'a') goto yy962; goto yy959; yy966: yych = *++p; if (yych == 'C') goto yy969; if (yych == 'c') goto yy969; goto yy959; yy967: yych = *++p; if (yych == ':') goto yy970; goto yy959; yy968: yych = *++p; if (yych == ':') goto yy972; goto yy959; yy969: yych = *++p; if (yych == 'R') goto yy973; if (yych == 'r') goto yy973; goto yy959; yy970: yyaccept = 1; yych = *(marker = ++p); if (yych == 'I') goto yy974; if (yych == 'i') goto yy974; yy971: { return (bufsize_t)(p - start); } yy972: ++p; goto yy971; yy973: yych = *++p; if (yych == 'I') goto yy975; if (yych == 'i') goto yy975; goto yy959; yy974: yych = *++p; if (yych == 'M') goto yy976; if (yych == 'm') goto yy976; goto yy959; yy975: yych = *++p; if (yych == 'P') goto yy977; if (yych == 'p') goto yy977; goto yy959; yy976: yych = *++p; if (yych == 'A') goto yy978; if (yych == 'a') goto yy978; goto yy959; yy977: yych = *++p; if (yych == 'T') goto yy968; if (yych == 't') goto yy968; goto yy959; yy978: yych = *++p; if (yych == 'G') goto yy979; if (yych != 'g') goto yy959; yy979: yych = *++p; if (yych == 'E') goto yy980; if (yych != 'e') goto yy959; yy980: yych = *++p; if (yych != '/') goto yy959; yych = *++p; if (yych <= 'W') { if (yych <= 'J') { if (yych == 'G') goto yy982; if (yych <= 'I') goto yy959; goto yy983; } else { if (yych == 'P') goto yy984; if (yych <= 'V') goto yy959; goto yy985; } } else { if (yych <= 'j') { if (yych == 'g') goto yy982; if (yych <= 'i') goto yy959; goto yy983; } else { if (yych <= 'p') { if (yych <= 'o') goto yy959; goto yy984; } else { if (yych == 'w') goto yy985; goto yy959; } } } yy982: yych = *++p; if (yych == 'I') goto yy986; if (yych == 'i') goto yy986; goto yy959; yy983: yych = *++p; if (yych == 'P') goto yy987; if (yych == 'p') goto yy987; goto yy959; yy984: yych = *++p; if (yych == 'N') goto yy988; if (yych == 'n') goto yy988; goto yy959; yy985: yych = *++p; if (yych == 'E') goto yy989; if (yych == 'e') goto yy989; goto yy959; yy986: yych = *++p; if (yych == 'F') goto yy990; if (yych == 'f') goto yy990; goto yy959; yy987: yych = *++p; if (yych == 'E') goto yy988; if (yych != 'e') goto yy959; yy988: yych = *++p; if (yych == 'G') goto yy990; if (yych == 'g') goto yy990; goto yy959; yy989: yych = *++p; if (yych == 'B') goto yy992; if (yych == 'b') goto yy992; goto yy959; yy990: ++p; { return 0; } yy992: yych = *++p; if (yych == 'P') goto yy990; if (yych == 'p') goto yy990; goto yy959; } } // Scans a footnote definition opening. bufsize_t _scan_footnote_definition(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 64, 64, 64, 64, 64, 64, 64, 64, 128, 0, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 128, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *p; if (yych == '[') goto yy997; ++p; yy996: { return 0; } yy997: yych = *(marker = ++p); if (yych != '^') goto yy996; yych = *++p; if (yych != ']') goto yy1001; yy999: p = marker; goto yy996; yy1000: yych = *++p; yy1001: if (yybm[0+yych] & 64) { goto yy1000; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= ' ') goto yy999; if (yych <= ']') goto yy1009; goto yy999; } else { if (yych <= 0xDF) goto yy1002; if (yych <= 0xE0) goto yy1003; goto yy1004; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy1005; if (yych <= 0xEF) goto yy1004; goto yy1006; } else { if (yych <= 0xF3) goto yy1007; if (yych <= 0xF4) goto yy1008; goto yy999; } } yy1002: yych = *++p; if (yych <= 0x7F) goto yy999; if (yych <= 0xBF) goto yy1000; goto yy999; yy1003: yych = *++p; if (yych <= 0x9F) goto yy999; if (yych <= 0xBF) goto yy1002; goto yy999; yy1004: yych = *++p; if (yych <= 0x7F) goto yy999; if (yych <= 0xBF) goto yy1002; goto yy999; yy1005: yych = *++p; if (yych <= 0x7F) goto yy999; if (yych <= 0x9F) goto yy1002; goto yy999; yy1006: yych = *++p; if (yych <= 0x8F) goto yy999; if (yych <= 0xBF) goto yy1004; goto yy999; yy1007: yych = *++p; if (yych <= 0x7F) goto yy999; if (yych <= 0xBF) goto yy1004; goto yy999; yy1008: yych = *++p; if (yych <= 0x7F) goto yy999; if (yych <= 0x8F) goto yy1004; goto yy999; yy1009: yych = *++p; if (yych != ':') goto yy999; yy1010: yych = *++p; if (yybm[0+yych] & 128) { goto yy1010; } { return (bufsize_t)(p - start); } } } cmark-gfm-0.1.8/cbits/html.c0000644000000000000000000003320113442034251013763 0ustar0000000000000000#include #include #include #include #include "cmark_ctype.h" #include "config.h" #include "cmark-gfm.h" #include "houdini.h" #include "scanners.h" #include "syntax_extension.h" #include "html.h" #include "render.h" // Functions to convert cmark_nodes to HTML strings. static void escape_html(cmark_strbuf *dest, const unsigned char *source, bufsize_t length) { houdini_escape_html0(dest, source, length, 0); } static void filter_html_block(cmark_html_renderer *renderer, uint8_t *data, size_t len) { cmark_strbuf *html = renderer->html; cmark_llist *it; cmark_syntax_extension *ext; bool filtered; uint8_t *match; while (len) { match = (uint8_t *) memchr(data, '<', len); if (!match) break; if (match != data) { cmark_strbuf_put(html, data, (bufsize_t)(match - data)); len -= (match - data); data = match; } filtered = false; for (it = renderer->filter_extensions; it; it = it->next) { ext = ((cmark_syntax_extension *) it->data); if (!ext->html_filter_func(ext, data, len)) { filtered = true; break; } } if (!filtered) { cmark_strbuf_putc(html, '<'); } else { cmark_strbuf_puts(html, "<"); } ++data; --len; } if (len) cmark_strbuf_put(html, data, (bufsize_t)len); } static bool S_put_footnote_backref(cmark_html_renderer *renderer, cmark_strbuf *html) { if (renderer->written_footnote_ix >= renderer->footnote_ix) return false; renderer->written_footnote_ix = renderer->footnote_ix; cmark_strbuf_puts(html, "footnote_ix); cmark_strbuf_puts(html, n); cmark_strbuf_puts(html, "\" class=\"footnote-backref\">↩"); return true; } static int S_render_node(cmark_html_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { cmark_node *parent; cmark_node *grandparent; cmark_strbuf *html = renderer->html; cmark_llist *it; cmark_syntax_extension *ext; char start_heading[] = "plain == node) { // back at original node renderer->plain = NULL; } if (renderer->plain != NULL) { switch (node->type) { case CMARK_NODE_TEXT: case CMARK_NODE_CODE: case CMARK_NODE_HTML_INLINE: escape_html(html, node->as.literal.data, node->as.literal.len); break; case CMARK_NODE_LINEBREAK: case CMARK_NODE_SOFTBREAK: cmark_strbuf_putc(html, ' '); break; default: break; } return 1; } if (node->extension && node->extension->html_render_func) { node->extension->html_render_func(node->extension, renderer, node, ev_type, options); return 1; } switch (node->type) { case CMARK_NODE_DOCUMENT: break; case CMARK_NODE_BLOCK_QUOTE: if (entering) { cmark_html_render_cr(html); cmark_strbuf_puts(html, "\n"); } else { cmark_html_render_cr(html); cmark_strbuf_puts(html, "\n"); } break; case CMARK_NODE_LIST: { cmark_list_type list_type = node->as.list.list_type; int start = node->as.list.start; if (entering) { cmark_html_render_cr(html); if (list_type == CMARK_BULLET_LIST) { cmark_strbuf_puts(html, "\n"); } else if (start == 1) { cmark_strbuf_puts(html, "\n"); } else { snprintf(buffer, BUFFER_SIZE, "
    \n"); } } else { cmark_strbuf_puts(html, list_type == CMARK_BULLET_LIST ? "\n" : "
\n"); } break; } case CMARK_NODE_ITEM: if (entering) { cmark_html_render_cr(html); cmark_strbuf_puts(html, "'); } else { cmark_strbuf_puts(html, "\n"); } break; case CMARK_NODE_HEADING: if (entering) { cmark_html_render_cr(html); start_heading[2] = (char)('0' + node->as.heading.level); cmark_strbuf_puts(html, start_heading); cmark_html_render_sourcepos(node, html, options); cmark_strbuf_putc(html, '>'); } else { end_heading[3] = (char)('0' + node->as.heading.level); cmark_strbuf_puts(html, end_heading); cmark_strbuf_puts(html, ">\n"); } break; case CMARK_NODE_CODE_BLOCK: cmark_html_render_cr(html); if (node->as.code.info.len == 0) { cmark_strbuf_puts(html, ""); } else { bufsize_t first_tag = 0; while (first_tag < node->as.code.info.len && !cmark_isspace(node->as.code.info.data[first_tag])) { first_tag += 1; } if (options & CMARK_OPT_GITHUB_PRE_LANG) { cmark_strbuf_puts(html, "as.code.info.data, first_tag); if (first_tag < node->as.code.info.len && (options & CMARK_OPT_FULL_INFO_STRING)) { cmark_strbuf_puts(html, "\" data-meta=\""); escape_html(html, node->as.code.info.data + first_tag + 1, node->as.code.info.len - first_tag - 1); } cmark_strbuf_puts(html, "\">"); } else { cmark_strbuf_puts(html, "as.code.info.data, first_tag); if (first_tag < node->as.code.info.len && (options & CMARK_OPT_FULL_INFO_STRING)) { cmark_strbuf_puts(html, "\" data-meta=\""); escape_html(html, node->as.code.info.data + first_tag + 1, node->as.code.info.len - first_tag - 1); } cmark_strbuf_puts(html, "\">"); } } escape_html(html, node->as.code.literal.data, node->as.code.literal.len); cmark_strbuf_puts(html, "\n"); break; case CMARK_NODE_HTML_BLOCK: cmark_html_render_cr(html); if (!(options & CMARK_OPT_UNSAFE)) { cmark_strbuf_puts(html, ""); } else if (renderer->filter_extensions) { filter_html_block(renderer, node->as.literal.data, node->as.literal.len); } else { cmark_strbuf_put(html, node->as.literal.data, node->as.literal.len); } cmark_html_render_cr(html); break; case CMARK_NODE_CUSTOM_BLOCK: cmark_html_render_cr(html); if (entering) { cmark_strbuf_put(html, node->as.custom.on_enter.data, node->as.custom.on_enter.len); } else { cmark_strbuf_put(html, node->as.custom.on_exit.data, node->as.custom.on_exit.len); } cmark_html_render_cr(html); break; case CMARK_NODE_THEMATIC_BREAK: cmark_html_render_cr(html); cmark_strbuf_puts(html, "\n"); break; case CMARK_NODE_PARAGRAPH: parent = cmark_node_parent(node); grandparent = cmark_node_parent(parent); if (grandparent != NULL && grandparent->type == CMARK_NODE_LIST) { tight = grandparent->as.list.tight; } else { tight = false; } if (!tight) { if (entering) { cmark_html_render_cr(html); cmark_strbuf_puts(html, "'); } else { if (parent->type == CMARK_NODE_FOOTNOTE_DEFINITION && node->next == NULL) { cmark_strbuf_putc(html, ' '); S_put_footnote_backref(renderer, html); } cmark_strbuf_puts(html, "

\n"); } } break; case CMARK_NODE_TEXT: escape_html(html, node->as.literal.data, node->as.literal.len); break; case CMARK_NODE_LINEBREAK: cmark_strbuf_puts(html, "
\n"); break; case CMARK_NODE_SOFTBREAK: if (options & CMARK_OPT_HARDBREAKS) { cmark_strbuf_puts(html, "
\n"); } else if (options & CMARK_OPT_NOBREAKS) { cmark_strbuf_putc(html, ' '); } else { cmark_strbuf_putc(html, '\n'); } break; case CMARK_NODE_CODE: cmark_strbuf_puts(html, ""); escape_html(html, node->as.literal.data, node->as.literal.len); cmark_strbuf_puts(html, ""); break; case CMARK_NODE_HTML_INLINE: if (!(options & CMARK_OPT_UNSAFE)) { cmark_strbuf_puts(html, ""); } else { filtered = false; for (it = renderer->filter_extensions; it; it = it->next) { ext = (cmark_syntax_extension *) it->data; if (!ext->html_filter_func(ext, node->as.literal.data, node->as.literal.len)) { filtered = true; break; } } if (!filtered) { cmark_strbuf_put(html, node->as.literal.data, node->as.literal.len); } else { cmark_strbuf_puts(html, "<"); cmark_strbuf_put(html, node->as.literal.data + 1, node->as.literal.len - 1); } } break; case CMARK_NODE_CUSTOM_INLINE: if (entering) { cmark_strbuf_put(html, node->as.custom.on_enter.data, node->as.custom.on_enter.len); } else { cmark_strbuf_put(html, node->as.custom.on_exit.data, node->as.custom.on_exit.len); } break; case CMARK_NODE_STRONG: if (entering) { cmark_strbuf_puts(html, ""); } else { cmark_strbuf_puts(html, ""); } break; case CMARK_NODE_EMPH: if (entering) { cmark_strbuf_puts(html, ""); } else { cmark_strbuf_puts(html, ""); } break; case CMARK_NODE_LINK: if (entering) { cmark_strbuf_puts(html, "as.link.url, 0))) { houdini_escape_href(html, node->as.link.url.data, node->as.link.url.len); } if (node->as.link.title.len) { cmark_strbuf_puts(html, "\" title=\""); escape_html(html, node->as.link.title.data, node->as.link.title.len); } cmark_strbuf_puts(html, "\">"); } else { cmark_strbuf_puts(html, ""); } break; case CMARK_NODE_IMAGE: if (entering) { cmark_strbuf_puts(html, "as.link.url, 0))) { houdini_escape_href(html, node->as.link.url.data, node->as.link.url.len); } cmark_strbuf_puts(html, "\" alt=\""); renderer->plain = node; } else { if (node->as.link.title.len) { cmark_strbuf_puts(html, "\" title=\""); escape_html(html, node->as.link.title.data, node->as.link.title.len); } cmark_strbuf_puts(html, "\" />"); } break; case CMARK_NODE_FOOTNOTE_DEFINITION: if (entering) { if (renderer->footnote_ix == 0) { cmark_strbuf_puts(html, "
\n
    \n"); } ++renderer->footnote_ix; cmark_strbuf_puts(html, "
  1. footnote_ix); cmark_strbuf_puts(html, n); cmark_strbuf_puts(html, "\">\n"); } else { if (S_put_footnote_backref(renderer, html)) { cmark_strbuf_putc(html, '\n'); } cmark_strbuf_puts(html, "
  2. \n"); } break; case CMARK_NODE_FOOTNOTE_REFERENCE: if (entering) { cmark_strbuf_puts(html, "as.literal.data, node->as.literal.len); cmark_strbuf_puts(html, "\" id=\"fnref"); cmark_strbuf_put(html, node->as.literal.data, node->as.literal.len); cmark_strbuf_puts(html, "\">"); cmark_strbuf_put(html, node->as.literal.data, node->as.literal.len); cmark_strbuf_puts(html, ""); } break; default: assert(false); break; } return 1; } char *cmark_render_html(cmark_node *root, int options, cmark_llist *extensions) { return cmark_render_html_with_mem(root, options, extensions, cmark_node_mem(root)); } char *cmark_render_html_with_mem(cmark_node *root, int options, cmark_llist *extensions, cmark_mem *mem) { char *result; cmark_strbuf html = CMARK_BUF_INIT(mem); cmark_event_type ev_type; cmark_node *cur; cmark_html_renderer renderer = {&html, NULL, NULL, 0, 0, NULL}; cmark_iter *iter = cmark_iter_new(root); for (; extensions; extensions = extensions->next) if (((cmark_syntax_extension *) extensions->data)->html_filter_func) renderer.filter_extensions = cmark_llist_append( mem, renderer.filter_extensions, (cmark_syntax_extension *) extensions->data); while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); S_render_node(&renderer, cur, ev_type, options); } if (renderer.footnote_ix) { cmark_strbuf_puts(&html, "
\n
\n"); } result = (char *)cmark_strbuf_detach(&html); cmark_llist_free(mem, renderer.filter_extensions); cmark_iter_free(iter); return result; } cmark-gfm-0.1.8/cbits/man.c0000644000000000000000000001411713442034251013577 0ustar0000000000000000#include #include #include #include #include "config.h" #include "cmark-gfm.h" #include "node.h" #include "buffer.h" #include "utf8.h" #include "render.h" #include "syntax_extension.h" #define OUT(s, wrap, escaping) renderer->out(renderer, node, s, wrap, escaping) #define LIT(s) renderer->out(renderer, node, s, false, LITERAL) #define CR() renderer->cr(renderer) #define BLANKLINE() renderer->blankline(renderer) #define LIST_NUMBER_SIZE 20 // Functions to convert cmark_nodes to groff man strings. static void S_outc(cmark_renderer *renderer, cmark_node *node, cmark_escaping escape, int32_t c, unsigned char nextc) { (void)(nextc); if (escape == LITERAL) { cmark_render_code_point(renderer, c); return; } switch (c) { case 46: if (renderer->begin_line) { cmark_render_ascii(renderer, "\\&."); } else { cmark_render_code_point(renderer, c); } break; case 39: if (renderer->begin_line) { cmark_render_ascii(renderer, "\\&'"); } else { cmark_render_code_point(renderer, c); } break; case 45: cmark_render_ascii(renderer, "\\-"); break; case 92: cmark_render_ascii(renderer, "\\e"); break; case 8216: // left single quote cmark_render_ascii(renderer, "\\[oq]"); break; case 8217: // right single quote cmark_render_ascii(renderer, "\\[cq]"); break; case 8220: // left double quote cmark_render_ascii(renderer, "\\[lq]"); break; case 8221: // right double quote cmark_render_ascii(renderer, "\\[rq]"); break; case 8212: // em dash cmark_render_ascii(renderer, "\\[em]"); break; case 8211: // en dash cmark_render_ascii(renderer, "\\[en]"); break; default: cmark_render_code_point(renderer, c); } } static int S_render_node(cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { cmark_node *tmp; int list_number; bool entering = (ev_type == CMARK_EVENT_ENTER); bool allow_wrap = renderer->width > 0 && !(CMARK_OPT_NOBREAKS & options); if (node->extension && node->extension->man_render_func) { node->extension->man_render_func(node->extension, renderer, node, ev_type, options); return 1; } switch (node->type) { case CMARK_NODE_DOCUMENT: if (entering) { /* Define a strikethrough macro */ /* Commenting out because this makes tests fail LIT(".de ST"); CR(); LIT(".nr ww \\w'\\\\$1'"); CR(); LIT("\\Z@\\v'-.25m'\\l'\\\\n[ww]u'@\\\\$1"); CR(); LIT(".."); CR(); */ } break; case CMARK_NODE_BLOCK_QUOTE: if (entering) { CR(); LIT(".RS"); CR(); } else { CR(); LIT(".RE"); CR(); } break; case CMARK_NODE_LIST: break; case CMARK_NODE_ITEM: if (entering) { CR(); LIT(".IP "); if (cmark_node_get_list_type(node->parent) == CMARK_BULLET_LIST) { LIT("\\[bu] 2"); } else { list_number = cmark_node_get_list_start(node->parent); tmp = node; while (tmp->prev) { tmp = tmp->prev; list_number += 1; } char list_number_s[LIST_NUMBER_SIZE]; snprintf(list_number_s, LIST_NUMBER_SIZE, "\"%d.\" 4", list_number); LIT(list_number_s); } CR(); } else { CR(); } break; case CMARK_NODE_HEADING: if (entering) { CR(); LIT(cmark_node_get_heading_level(node) == 1 ? ".SH" : ".SS"); CR(); } else { CR(); } break; case CMARK_NODE_CODE_BLOCK: CR(); LIT(".IP\n.nf\n\\f[C]\n"); OUT(cmark_node_get_literal(node), false, NORMAL); CR(); LIT("\\f[]\n.fi"); CR(); break; case CMARK_NODE_HTML_BLOCK: break; case CMARK_NODE_CUSTOM_BLOCK: CR(); OUT(entering ? cmark_node_get_on_enter(node) : cmark_node_get_on_exit(node), false, LITERAL); CR(); break; case CMARK_NODE_THEMATIC_BREAK: CR(); LIT(".PP\n * * * * *"); CR(); break; case CMARK_NODE_PARAGRAPH: if (entering) { // no blank line if first paragraph in list: if (node->parent && node->parent->type == CMARK_NODE_ITEM && node->prev == NULL) { // no blank line or .PP } else { CR(); LIT(".PP"); CR(); } } else { CR(); } break; case CMARK_NODE_TEXT: OUT(cmark_node_get_literal(node), allow_wrap, NORMAL); break; case CMARK_NODE_LINEBREAK: LIT(".PD 0\n.P\n.PD"); CR(); break; case CMARK_NODE_SOFTBREAK: if (options & CMARK_OPT_HARDBREAKS) { LIT(".PD 0\n.P\n.PD"); CR(); } else if (renderer->width == 0 && !(CMARK_OPT_NOBREAKS & options)) { CR(); } else { OUT(" ", allow_wrap, LITERAL); } break; case CMARK_NODE_CODE: LIT("\\f[C]"); OUT(cmark_node_get_literal(node), allow_wrap, NORMAL); LIT("\\f[]"); break; case CMARK_NODE_HTML_INLINE: break; case CMARK_NODE_CUSTOM_INLINE: OUT(entering ? cmark_node_get_on_enter(node) : cmark_node_get_on_exit(node), false, LITERAL); break; case CMARK_NODE_STRONG: if (entering) { LIT("\\f[B]"); } else { LIT("\\f[]"); } break; case CMARK_NODE_EMPH: if (entering) { LIT("\\f[I]"); } else { LIT("\\f[]"); } break; case CMARK_NODE_LINK: if (!entering) { LIT(" ("); OUT(cmark_node_get_url(node), allow_wrap, URL); LIT(")"); } break; case CMARK_NODE_IMAGE: if (entering) { LIT("[IMAGE: "); } else { LIT("]"); } break; case CMARK_NODE_FOOTNOTE_DEFINITION: case CMARK_NODE_FOOTNOTE_REFERENCE: // TODO break; default: assert(false); break; } return 1; } char *cmark_render_man(cmark_node *root, int options, int width) { return cmark_render_man_with_mem(root, options, width, cmark_node_mem(root)); } char *cmark_render_man_with_mem(cmark_node *root, int options, int width, cmark_mem *mem) { return cmark_render(mem, root, options, width, S_outc, S_render_node); } cmark-gfm-0.1.8/cbits/commonmark.c0000644000000000000000000003360413442037162015175 0ustar0000000000000000#include #include #include #include #include #include "config.h" #include "cmark-gfm.h" #include "node.h" #include "buffer.h" #include "utf8.h" #include "scanners.h" #include "render.h" #include "syntax_extension.h" #define OUT(s, wrap, escaping) renderer->out(renderer, node, s, wrap, escaping) #define LIT(s) renderer->out(renderer, node, s, false, LITERAL) #define CR() renderer->cr(renderer) #define BLANKLINE() renderer->blankline(renderer) #define ENCODED_SIZE 20 #define LISTMARKER_SIZE 20 // Functions to convert cmark_nodes to commonmark strings. static CMARK_INLINE void outc(cmark_renderer *renderer, cmark_node *node, cmark_escaping escape, int32_t c, unsigned char nextc) { bool needs_escaping = false; bool follows_digit = renderer->buffer->size > 0 && cmark_isdigit(renderer->buffer->ptr[renderer->buffer->size - 1]); char encoded[ENCODED_SIZE]; needs_escaping = c < 0x80 && escape != LITERAL && ((escape == NORMAL && (c == '*' || c == '_' || c == '[' || c == ']' || c == '#' || c == '<' || c == '>' || c == '\\' || c == '`' || c == '~' || c == '!' || (c == '&' && cmark_isalpha(nextc)) || (c == '!' && nextc == '[') || (renderer->begin_content && (c == '-' || c == '+' || c == '=') && // begin_content doesn't get set to false til we've passed digits // at the beginning of line, so... !follows_digit) || (renderer->begin_content && (c == '.' || c == ')') && follows_digit && (nextc == 0 || cmark_isspace(nextc))))) || (escape == URL && (c == '`' || c == '<' || c == '>' || cmark_isspace((char)c) || c == '\\' || c == ')' || c == '(')) || (escape == TITLE && (c == '`' || c == '<' || c == '>' || c == '"' || c == '\\'))); if (needs_escaping) { if (cmark_isspace((char)c)) { // use percent encoding for spaces snprintf(encoded, ENCODED_SIZE, "%%%2x", c); cmark_strbuf_puts(renderer->buffer, encoded); renderer->column += 3; } else { cmark_render_ascii(renderer, "\\"); cmark_render_code_point(renderer, c); } } else { cmark_render_code_point(renderer, c); } } static int longest_backtick_sequence(const char *code) { int longest = 0; int current = 0; size_t i = 0; size_t code_len = strlen(code); while (i <= code_len) { if (code[i] == '`') { current++; } else { if (current > longest) { longest = current; } current = 0; } i++; } return longest; } static int shortest_unused_backtick_sequence(const char *code) { // note: if the shortest sequence is >= 32, this returns 32 // so as not to overflow the bit array. uint32_t used = 1; int current = 0; size_t i = 0; size_t code_len = strlen(code); while (i <= code_len) { if (code[i] == '`') { current++; } else { if (current > 0 && current < 32) { used |= (1U << current); } current = 0; } i++; } // return number of first bit that is 0: i = 0; while (i < 32 && used & 1) { used = used >> 1; i++; } return (int)i; } static bool is_autolink(cmark_node *node) { cmark_chunk *title; cmark_chunk *url; cmark_node *link_text; char *realurl; int realurllen; if (node->type != CMARK_NODE_LINK) { return false; } url = &node->as.link.url; if (url->len == 0 || scan_scheme(url, 0) == 0) { return false; } title = &node->as.link.title; // if it has a title, we can't treat it as an autolink: if (title->len > 0) { return false; } link_text = node->first_child; if (link_text == NULL) { return false; } cmark_consolidate_text_nodes(link_text); realurl = (char *)url->data; realurllen = url->len; if (strncmp(realurl, "mailto:", 7) == 0) { realurl += 7; realurllen -= 7; } return (realurllen == link_text->as.literal.len && strncmp(realurl, (char *)link_text->as.literal.data, link_text->as.literal.len) == 0); } // if node is a block node, returns node. // otherwise returns first block-level node that is an ancestor of node. // if there is no block-level ancestor, returns NULL. static cmark_node *get_containing_block(cmark_node *node) { while (node) { if (CMARK_NODE_BLOCK_P(node)) { return node; } else { node = node->parent; } } return NULL; } static int S_render_node(cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { cmark_node *tmp; int list_number; cmark_delim_type list_delim; int numticks; bool extra_spaces; int i; bool entering = (ev_type == CMARK_EVENT_ENTER); const char *info, *code, *title; char fencechar[2] = {'\0', '\0'}; size_t info_len, code_len; char listmarker[LISTMARKER_SIZE]; char *emph_delim; bool first_in_list_item; bufsize_t marker_width; bool allow_wrap = renderer->width > 0 && !(CMARK_OPT_NOBREAKS & options) && !(CMARK_OPT_HARDBREAKS & options); // Don't adjust tight list status til we've started the list. // Otherwise we loose the blank line between a paragraph and // a following list. if (!(node->type == CMARK_NODE_ITEM && node->prev == NULL && entering)) { tmp = get_containing_block(node); renderer->in_tight_list_item = tmp && // tmp might be NULL if there is no containing block ((tmp->type == CMARK_NODE_ITEM && cmark_node_get_list_tight(tmp->parent)) || (tmp && tmp->parent && tmp->parent->type == CMARK_NODE_ITEM && cmark_node_get_list_tight(tmp->parent->parent))); } if (node->extension && node->extension->commonmark_render_func) { node->extension->commonmark_render_func(node->extension, renderer, node, ev_type, options); return 1; } switch (node->type) { case CMARK_NODE_DOCUMENT: break; case CMARK_NODE_BLOCK_QUOTE: if (entering) { LIT("> "); renderer->begin_content = true; cmark_strbuf_puts(renderer->prefix, "> "); } else { cmark_strbuf_truncate(renderer->prefix, renderer->prefix->size - 2); BLANKLINE(); } break; case CMARK_NODE_LIST: if (!entering && node->next && (node->next->type == CMARK_NODE_CODE_BLOCK || node->next->type == CMARK_NODE_LIST)) { // this ensures that a following indented code block or list will be // inteprereted correctly. CR(); LIT(""); BLANKLINE(); } break; case CMARK_NODE_ITEM: if (cmark_node_get_list_type(node->parent) == CMARK_BULLET_LIST) { marker_width = 4; } else { list_number = cmark_node_get_list_start(node->parent); list_delim = cmark_node_get_list_delim(node->parent); tmp = node; while (tmp->prev) { tmp = tmp->prev; list_number += 1; } // we ensure a width of at least 4 so // we get nice transition from single digits // to double snprintf(listmarker, LISTMARKER_SIZE, "%d%s%s", list_number, list_delim == CMARK_PAREN_DELIM ? ")" : ".", list_number < 10 ? " " : " "); marker_width = (bufsize_t)strlen(listmarker); } if (entering) { if (cmark_node_get_list_type(node->parent) == CMARK_BULLET_LIST) { LIT(" - "); renderer->begin_content = true; } else { LIT(listmarker); renderer->begin_content = true; } for (i = marker_width; i--;) { cmark_strbuf_putc(renderer->prefix, ' '); } } else { cmark_strbuf_truncate(renderer->prefix, renderer->prefix->size - marker_width); CR(); } break; case CMARK_NODE_HEADING: if (entering) { for (i = cmark_node_get_heading_level(node); i > 0; i--) { LIT("#"); } LIT(" "); renderer->begin_content = true; renderer->no_linebreaks = true; } else { renderer->no_linebreaks = false; BLANKLINE(); } break; case CMARK_NODE_CODE_BLOCK: first_in_list_item = node->prev == NULL && node->parent && node->parent->type == CMARK_NODE_ITEM; if (!first_in_list_item) { BLANKLINE(); } info = cmark_node_get_fence_info(node); info_len = strlen(info); fencechar[0] = strchr(info, '`') == NULL ? '`' : '~'; code = cmark_node_get_literal(node); code_len = strlen(code); // use indented form if no info, and code doesn't // begin or end with a blank line, and code isn't // first thing in a list item if (info_len == 0 && (code_len > 2 && !cmark_isspace(code[0]) && !(cmark_isspace(code[code_len - 1]) && cmark_isspace(code[code_len - 2]))) && !first_in_list_item) { LIT(" "); cmark_strbuf_puts(renderer->prefix, " "); OUT(cmark_node_get_literal(node), false, LITERAL); cmark_strbuf_truncate(renderer->prefix, renderer->prefix->size - 4); } else { numticks = longest_backtick_sequence(code) + 1; if (numticks < 3) { numticks = 3; } for (i = 0; i < numticks; i++) { LIT(fencechar); } LIT(" "); OUT(info, false, LITERAL); CR(); OUT(cmark_node_get_literal(node), false, LITERAL); CR(); for (i = 0; i < numticks; i++) { LIT(fencechar); } } BLANKLINE(); break; case CMARK_NODE_HTML_BLOCK: BLANKLINE(); OUT(cmark_node_get_literal(node), false, LITERAL); BLANKLINE(); break; case CMARK_NODE_CUSTOM_BLOCK: BLANKLINE(); OUT(entering ? cmark_node_get_on_enter(node) : cmark_node_get_on_exit(node), false, LITERAL); BLANKLINE(); break; case CMARK_NODE_THEMATIC_BREAK: BLANKLINE(); LIT("-----"); BLANKLINE(); break; case CMARK_NODE_PARAGRAPH: if (!entering) { BLANKLINE(); } break; case CMARK_NODE_TEXT: OUT(cmark_node_get_literal(node), allow_wrap, NORMAL); break; case CMARK_NODE_LINEBREAK: if (!(CMARK_OPT_HARDBREAKS & options)) { LIT(" "); } CR(); break; case CMARK_NODE_SOFTBREAK: if (CMARK_OPT_HARDBREAKS & options) { LIT(" "); CR(); } else if (!renderer->no_linebreaks && renderer->width == 0 && !(CMARK_OPT_HARDBREAKS & options) && !(CMARK_OPT_NOBREAKS & options)) { CR(); } else { OUT(" ", allow_wrap, LITERAL); } break; case CMARK_NODE_CODE: code = cmark_node_get_literal(node); code_len = strlen(code); numticks = shortest_unused_backtick_sequence(code); extra_spaces = code_len == 0 || code[0] == '`' || code[code_len - 1] == '`' || code[0] == ' ' || code[code_len - 1] == ' '; for (i = 0; i < numticks; i++) { LIT("`"); } if (extra_spaces) { LIT(" "); } OUT(cmark_node_get_literal(node), allow_wrap, LITERAL); if (extra_spaces) { LIT(" "); } for (i = 0; i < numticks; i++) { LIT("`"); } break; case CMARK_NODE_HTML_INLINE: OUT(cmark_node_get_literal(node), false, LITERAL); break; case CMARK_NODE_CUSTOM_INLINE: OUT(entering ? cmark_node_get_on_enter(node) : cmark_node_get_on_exit(node), false, LITERAL); break; case CMARK_NODE_STRONG: if (entering) { LIT("**"); } else { LIT("**"); } break; case CMARK_NODE_EMPH: // If we have EMPH(EMPH(x)), we need to use *_x_* // because **x** is STRONG(x): if (node->parent && node->parent->type == CMARK_NODE_EMPH && node->next == NULL && node->prev == NULL) { emph_delim = "_"; } else { emph_delim = "*"; } if (entering) { LIT(emph_delim); } else { LIT(emph_delim); } break; case CMARK_NODE_LINK: if (is_autolink(node)) { if (entering) { LIT("<"); if (strncmp(cmark_node_get_url(node), "mailto:", 7) == 0) { LIT((const char *)cmark_node_get_url(node) + 7); } else { LIT((const char *)cmark_node_get_url(node)); } LIT(">"); // return signal to skip contents of node... return 0; } } else { if (entering) { LIT("["); } else { LIT("]("); OUT(cmark_node_get_url(node), false, URL); title = cmark_node_get_title(node); if (strlen(title) > 0) { LIT(" \""); OUT(title, false, TITLE); LIT("\""); } LIT(")"); } } break; case CMARK_NODE_IMAGE: if (entering) { LIT("!["); } else { LIT("]("); OUT(cmark_node_get_url(node), false, URL); title = cmark_node_get_title(node); if (strlen(title) > 0) { OUT(" \"", allow_wrap, LITERAL); OUT(title, false, TITLE); LIT("\""); } LIT(")"); } break; case CMARK_NODE_FOOTNOTE_REFERENCE: if (entering) { LIT("[^"); OUT(cmark_chunk_to_cstr(renderer->mem, &node->as.literal), false, LITERAL); LIT("]"); } break; case CMARK_NODE_FOOTNOTE_DEFINITION: if (entering) { renderer->footnote_ix += 1; LIT("[^"); char n[32]; snprintf(n, sizeof(n), "%d", renderer->footnote_ix); OUT(n, false, LITERAL); LIT("]:\n"); cmark_strbuf_puts(renderer->prefix, " "); } else { cmark_strbuf_truncate(renderer->prefix, renderer->prefix->size - 4); } break; default: assert(false); break; } return 1; } char *cmark_render_commonmark(cmark_node *root, int options, int width) { return cmark_render_commonmark_with_mem(root, options, width, cmark_node_mem(root)); } char *cmark_render_commonmark_with_mem(cmark_node *root, int options, int width, cmark_mem *mem) { if (options & CMARK_OPT_HARDBREAKS) { // disable breaking on width, since it has // a different meaning with OPT_HARDBREAKS width = 0; } return cmark_render(mem, root, options, width, outc, S_render_node); } cmark-gfm-0.1.8/cbits/latex.c0000644000000000000000000002534313442034251014144 0ustar0000000000000000#include #include #include #include #include "config.h" #include "cmark-gfm.h" #include "node.h" #include "buffer.h" #include "utf8.h" #include "scanners.h" #include "render.h" #include "syntax_extension.h" #define OUT(s, wrap, escaping) renderer->out(renderer, node, s, wrap, escaping) #define LIT(s) renderer->out(renderer, node, s, false, LITERAL) #define CR() renderer->cr(renderer) #define BLANKLINE() renderer->blankline(renderer) #define LIST_NUMBER_STRING_SIZE 20 static CMARK_INLINE void outc(cmark_renderer *renderer, cmark_node *node, cmark_escaping escape, int32_t c, unsigned char nextc) { if (escape == LITERAL) { cmark_render_code_point(renderer, c); return; } switch (c) { case 123: // '{' case 125: // '}' case 35: // '#' case 37: // '%' case 38: // '&' cmark_render_ascii(renderer, "\\"); cmark_render_code_point(renderer, c); break; case 36: // '$' case 95: // '_' if (escape == NORMAL) { cmark_render_ascii(renderer, "\\"); } cmark_render_code_point(renderer, c); break; case 45: // '-' if (nextc == 45) { // prevent ligature cmark_render_ascii(renderer, "-{}"); } else { cmark_render_ascii(renderer, "-"); } break; case 126: // '~' if (escape == NORMAL) { cmark_render_ascii(renderer, "\\textasciitilde{}"); } else { cmark_render_code_point(renderer, c); } break; case 94: // '^' cmark_render_ascii(renderer, "\\^{}"); break; case 92: // '\\' if (escape == URL) { // / acts as path sep even on windows: cmark_render_ascii(renderer, "/"); } else { cmark_render_ascii(renderer, "\\textbackslash{}"); } break; case 124: // '|' cmark_render_ascii(renderer, "\\textbar{}"); break; case 60: // '<' cmark_render_ascii(renderer, "\\textless{}"); break; case 62: // '>' cmark_render_ascii(renderer, "\\textgreater{}"); break; case 91: // '[' case 93: // ']' cmark_render_ascii(renderer, "{"); cmark_render_code_point(renderer, c); cmark_render_ascii(renderer, "}"); break; case 34: // '"' cmark_render_ascii(renderer, "\\textquotedbl{}"); // requires \usepackage[T1]{fontenc} break; case 39: // '\'' cmark_render_ascii(renderer, "\\textquotesingle{}"); // requires \usepackage{textcomp} break; case 160: // nbsp cmark_render_ascii(renderer, "~"); break; case 8230: // hellip cmark_render_ascii(renderer, "\\ldots{}"); break; case 8216: // lsquo if (escape == NORMAL) { cmark_render_ascii(renderer, "`"); } else { cmark_render_code_point(renderer, c); } break; case 8217: // rsquo if (escape == NORMAL) { cmark_render_ascii(renderer, "\'"); } else { cmark_render_code_point(renderer, c); } break; case 8220: // ldquo if (escape == NORMAL) { cmark_render_ascii(renderer, "``"); } else { cmark_render_code_point(renderer, c); } break; case 8221: // rdquo if (escape == NORMAL) { cmark_render_ascii(renderer, "''"); } else { cmark_render_code_point(renderer, c); } break; case 8212: // emdash if (escape == NORMAL) { cmark_render_ascii(renderer, "---"); } else { cmark_render_code_point(renderer, c); } break; case 8211: // endash if (escape == NORMAL) { cmark_render_ascii(renderer, "--"); } else { cmark_render_code_point(renderer, c); } break; default: cmark_render_code_point(renderer, c); } } typedef enum { NO_LINK, URL_AUTOLINK, EMAIL_AUTOLINK, NORMAL_LINK, INTERNAL_LINK } link_type; static link_type get_link_type(cmark_node *node) { size_t title_len, url_len; cmark_node *link_text; char *realurl; int realurllen; bool isemail = false; if (node->type != CMARK_NODE_LINK) { return NO_LINK; } const char *url = cmark_node_get_url(node); cmark_chunk url_chunk = cmark_chunk_literal(url); if (url && *url == '#') { return INTERNAL_LINK; } url_len = strlen(url); if (url_len == 0 || scan_scheme(&url_chunk, 0) == 0) { return NO_LINK; } const char *title = cmark_node_get_title(node); title_len = strlen(title); // if it has a title, we can't treat it as an autolink: if (title_len == 0) { link_text = node->first_child; cmark_consolidate_text_nodes(link_text); if (!link_text) return NO_LINK; realurl = (char *)url; realurllen = (int)url_len; if (strncmp(realurl, "mailto:", 7) == 0) { realurl += 7; realurllen -= 7; isemail = true; } if (realurllen == link_text->as.literal.len && strncmp(realurl, (char *)link_text->as.literal.data, link_text->as.literal.len) == 0) { if (isemail) { return EMAIL_AUTOLINK; } else { return URL_AUTOLINK; } } } return NORMAL_LINK; } static int S_get_enumlevel(cmark_node *node) { int enumlevel = 0; cmark_node *tmp = node; while (tmp) { if (tmp->type == CMARK_NODE_LIST && cmark_node_get_list_type(node) == CMARK_ORDERED_LIST) { enumlevel++; } tmp = tmp->parent; } return enumlevel; } static int S_render_node(cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { int list_number; int enumlevel; char list_number_string[LIST_NUMBER_STRING_SIZE]; bool entering = (ev_type == CMARK_EVENT_ENTER); cmark_list_type list_type; bool allow_wrap = renderer->width > 0 && !(CMARK_OPT_NOBREAKS & options); if (node->extension && node->extension->latex_render_func) { node->extension->latex_render_func(node->extension, renderer, node, ev_type, options); return 1; } switch (node->type) { case CMARK_NODE_DOCUMENT: break; case CMARK_NODE_BLOCK_QUOTE: if (entering) { LIT("\\begin{quote}"); CR(); } else { LIT("\\end{quote}"); BLANKLINE(); } break; case CMARK_NODE_LIST: list_type = cmark_node_get_list_type(node); if (entering) { LIT("\\begin{"); LIT(list_type == CMARK_ORDERED_LIST ? "enumerate" : "itemize"); LIT("}"); CR(); list_number = cmark_node_get_list_start(node); if (list_number > 1) { enumlevel = S_get_enumlevel(node); // latex normally supports only five levels if (enumlevel >= 1 && enumlevel <= 5) { snprintf(list_number_string, LIST_NUMBER_STRING_SIZE, "%d", list_number); LIT("\\setcounter{enum"); switch (enumlevel) { case 1: LIT("i"); break; case 2: LIT("ii"); break; case 3: LIT("iii"); break; case 4: LIT("iv"); break; case 5: LIT("v"); break; default: LIT("i"); break; } LIT("}{"); OUT(list_number_string, false, NORMAL); LIT("}"); } CR(); } } else { LIT("\\end{"); LIT(list_type == CMARK_ORDERED_LIST ? "enumerate" : "itemize"); LIT("}"); BLANKLINE(); } break; case CMARK_NODE_ITEM: if (entering) { LIT("\\item "); } else { CR(); } break; case CMARK_NODE_HEADING: if (entering) { switch (cmark_node_get_heading_level(node)) { case 1: LIT("\\section"); break; case 2: LIT("\\subsection"); break; case 3: LIT("\\subsubsection"); break; case 4: LIT("\\paragraph"); break; case 5: LIT("\\subparagraph"); break; } LIT("{"); } else { LIT("}"); BLANKLINE(); } break; case CMARK_NODE_CODE_BLOCK: CR(); LIT("\\begin{verbatim}"); CR(); OUT(cmark_node_get_literal(node), false, LITERAL); CR(); LIT("\\end{verbatim}"); BLANKLINE(); break; case CMARK_NODE_HTML_BLOCK: break; case CMARK_NODE_CUSTOM_BLOCK: CR(); OUT(entering ? cmark_node_get_on_enter(node) : cmark_node_get_on_exit(node), false, LITERAL); CR(); break; case CMARK_NODE_THEMATIC_BREAK: BLANKLINE(); LIT("\\begin{center}\\rule{0.5\\linewidth}{\\linethickness}\\end{center}"); BLANKLINE(); break; case CMARK_NODE_PARAGRAPH: if (!entering) { BLANKLINE(); } break; case CMARK_NODE_TEXT: OUT(cmark_node_get_literal(node), allow_wrap, NORMAL); break; case CMARK_NODE_LINEBREAK: LIT("\\\\"); CR(); break; case CMARK_NODE_SOFTBREAK: if (options & CMARK_OPT_HARDBREAKS) { LIT("\\\\"); CR(); } else if (renderer->width == 0 && !(CMARK_OPT_NOBREAKS & options)) { CR(); } else { OUT(" ", allow_wrap, NORMAL); } break; case CMARK_NODE_CODE: LIT("\\texttt{"); OUT(cmark_node_get_literal(node), false, NORMAL); LIT("}"); break; case CMARK_NODE_HTML_INLINE: break; case CMARK_NODE_CUSTOM_INLINE: OUT(entering ? cmark_node_get_on_enter(node) : cmark_node_get_on_exit(node), false, LITERAL); break; case CMARK_NODE_STRONG: if (entering) { LIT("\\textbf{"); } else { LIT("}"); } break; case CMARK_NODE_EMPH: if (entering) { LIT("\\emph{"); } else { LIT("}"); } break; case CMARK_NODE_LINK: if (entering) { const char *url = cmark_node_get_url(node); // requires \usepackage{hyperref} switch (get_link_type(node)) { case URL_AUTOLINK: LIT("\\url{"); OUT(url, false, URL); LIT("}"); return 0; // Don't process further nodes to avoid double-rendering artefacts case EMAIL_AUTOLINK: LIT("\\href{"); OUT(url, false, URL); LIT("}\\nolinkurl{"); break; case NORMAL_LINK: LIT("\\href{"); OUT(url, false, URL); LIT("}{"); break; case INTERNAL_LINK: LIT("\\protect\\hyperlink{"); OUT(url + 1, false, URL); LIT("}{"); break; case NO_LINK: LIT("{"); // error? } } else { LIT("}"); } break; case CMARK_NODE_IMAGE: if (entering) { LIT("\\protect\\includegraphics{"); // requires \include{graphicx} OUT(cmark_node_get_url(node), false, URL); LIT("}"); return 0; } break; case CMARK_NODE_FOOTNOTE_DEFINITION: case CMARK_NODE_FOOTNOTE_REFERENCE: // TODO break; default: assert(false); break; } return 1; } char *cmark_render_latex(cmark_node *root, int options, int width) { return cmark_render_latex_with_mem(root, options, width, cmark_node_mem(root)); } char *cmark_render_latex_with_mem(cmark_node *root, int options, int width, cmark_mem *mem) { return cmark_render(mem, root, options, width, outc, S_render_node); } cmark-gfm-0.1.8/cbits/xml.c0000644000000000000000000001317413442034251013626 0ustar0000000000000000#include #include #include #include #include "config.h" #include "cmark-gfm.h" #include "node.h" #include "buffer.h" #include "houdini.h" #include "syntax_extension.h" #define BUFFER_SIZE 100 // Functions to convert cmark_nodes to XML strings. static void escape_xml(cmark_strbuf *dest, const unsigned char *source, bufsize_t length) { houdini_escape_html0(dest, source, length, 0); } struct render_state { cmark_strbuf *xml; int indent; }; static CMARK_INLINE void indent(struct render_state *state) { int i; for (i = 0; i < state->indent; i++) { cmark_strbuf_putc(state->xml, ' '); } } static int S_render_node(cmark_node *node, cmark_event_type ev_type, struct render_state *state, int options) { cmark_strbuf *xml = state->xml; bool literal = false; cmark_delim_type delim; bool entering = (ev_type == CMARK_EVENT_ENTER); char buffer[BUFFER_SIZE]; if (entering) { indent(state); cmark_strbuf_putc(xml, '<'); cmark_strbuf_puts(xml, cmark_node_get_type_string(node)); if (options & CMARK_OPT_SOURCEPOS && node->start_line != 0) { snprintf(buffer, BUFFER_SIZE, " sourcepos=\"%d:%d-%d:%d\"", node->start_line, node->start_column, node->end_line, node->end_column); cmark_strbuf_puts(xml, buffer); } if (node->extension && node->extension->xml_attr_func) { const char* r = node->extension->xml_attr_func(node->extension, node); if (r != NULL) cmark_strbuf_puts(xml, r); } literal = false; switch (node->type) { case CMARK_NODE_DOCUMENT: cmark_strbuf_puts(xml, " xmlns=\"http://commonmark.org/xml/1.0\""); break; case CMARK_NODE_TEXT: case CMARK_NODE_CODE: case CMARK_NODE_HTML_BLOCK: case CMARK_NODE_HTML_INLINE: cmark_strbuf_puts(xml, " xml:space=\"preserve\">"); escape_xml(xml, node->as.literal.data, node->as.literal.len); cmark_strbuf_puts(xml, "as.heading.level); cmark_strbuf_puts(xml, buffer); break; case CMARK_NODE_CODE_BLOCK: if (node->as.code.info.len > 0) { cmark_strbuf_puts(xml, " info=\""); escape_xml(xml, node->as.code.info.data, node->as.code.info.len); cmark_strbuf_putc(xml, '"'); } cmark_strbuf_puts(xml, " xml:space=\"preserve\">"); escape_xml(xml, node->as.code.literal.data, node->as.code.literal.len); cmark_strbuf_puts(xml, "as.custom.on_enter.data, node->as.custom.on_enter.len); cmark_strbuf_putc(xml, '"'); cmark_strbuf_puts(xml, " on_exit=\""); escape_xml(xml, node->as.custom.on_exit.data, node->as.custom.on_exit.len); cmark_strbuf_putc(xml, '"'); break; case CMARK_NODE_LINK: case CMARK_NODE_IMAGE: cmark_strbuf_puts(xml, " destination=\""); escape_xml(xml, node->as.link.url.data, node->as.link.url.len); cmark_strbuf_putc(xml, '"'); cmark_strbuf_puts(xml, " title=\""); escape_xml(xml, node->as.link.title.data, node->as.link.title.len); cmark_strbuf_putc(xml, '"'); break; default: break; } if (node->first_child) { state->indent += 2; } else if (!literal) { cmark_strbuf_puts(xml, " /"); } cmark_strbuf_puts(xml, ">\n"); } else if (node->first_child) { state->indent -= 2; indent(state); cmark_strbuf_puts(xml, "\n"); } return 1; } char *cmark_render_xml(cmark_node *root, int options) { return cmark_render_xml_with_mem(root, options, cmark_node_mem(root)); } char *cmark_render_xml_with_mem(cmark_node *root, int options, cmark_mem *mem) { char *result; cmark_strbuf xml = CMARK_BUF_INIT(mem); cmark_event_type ev_type; cmark_node *cur; struct render_state state = {&xml, 0}; cmark_iter *iter = cmark_iter_new(root); cmark_strbuf_puts(state.xml, "\n"); cmark_strbuf_puts(state.xml, "\n"); while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); S_render_node(cur, ev_type, &state, options); } result = (char *)cmark_strbuf_detach(&xml); cmark_iter_free(iter); return result; } cmark-gfm-0.1.8/cbits/render.c0000644000000000000000000001513613442037162014311 0ustar0000000000000000#include #include "buffer.h" #include "chunk.h" #include "cmark-gfm.h" #include "utf8.h" #include "render.h" #include "node.h" #include "syntax_extension.h" static CMARK_INLINE void S_cr(cmark_renderer *renderer) { if (renderer->need_cr < 1) { renderer->need_cr = 1; } } static CMARK_INLINE void S_blankline(cmark_renderer *renderer) { if (renderer->need_cr < 2) { renderer->need_cr = 2; } } static void S_out(cmark_renderer *renderer, cmark_node *node, const char *source, bool wrap, cmark_escaping escape) { int length = (int)strlen(source); unsigned char nextc; int32_t c; int i = 0; int last_nonspace; int len; cmark_chunk remainder = cmark_chunk_literal(""); int k = renderer->buffer->size - 1; cmark_syntax_extension *ext = NULL; cmark_node *n = node; while (n && !ext) { ext = n->extension; if (!ext) n = n->parent; } if (ext && !ext->commonmark_escape_func) ext = NULL; wrap = wrap && !renderer->no_linebreaks; if (renderer->in_tight_list_item && renderer->need_cr > 1) { renderer->need_cr = 1; } while (renderer->need_cr) { if (k < 0 || renderer->buffer->ptr[k] == '\n') { k -= 1; } else { cmark_strbuf_putc(renderer->buffer, '\n'); if (renderer->need_cr > 1) { cmark_strbuf_put(renderer->buffer, renderer->prefix->ptr, renderer->prefix->size); } } renderer->column = 0; renderer->last_breakable = 0; renderer->begin_line = true; renderer->begin_content = true; renderer->need_cr -= 1; } while (i < length) { if (renderer->begin_line) { cmark_strbuf_put(renderer->buffer, renderer->prefix->ptr, renderer->prefix->size); // note: this assumes prefix is ascii: renderer->column = renderer->prefix->size; } len = cmark_utf8proc_iterate((const uint8_t *)source + i, length - i, &c); if (len == -1) { // error condition return; // return without rendering rest of string } if (ext && ext->commonmark_escape_func(ext, node, c)) cmark_strbuf_putc(renderer->buffer, '\\'); nextc = source[i + len]; if (c == 32 && wrap) { if (!renderer->begin_line) { last_nonspace = renderer->buffer->size; cmark_strbuf_putc(renderer->buffer, ' '); renderer->column += 1; renderer->begin_line = false; renderer->begin_content = false; // skip following spaces while (source[i + 1] == ' ') { i++; } // We don't allow breaks that make a digit the first character // because this causes problems with commonmark output. if (!cmark_isdigit(source[i + 1])) { renderer->last_breakable = last_nonspace; } } } else if (c == 10) { cmark_strbuf_putc(renderer->buffer, '\n'); renderer->column = 0; renderer->begin_line = true; renderer->begin_content = true; renderer->last_breakable = 0; } else if (escape == LITERAL) { cmark_render_code_point(renderer, c); renderer->begin_line = false; // we don't set 'begin_content' to false til we've // finished parsing a digit. Reason: in commonmark // we need to escape a potential list marker after // a digit: renderer->begin_content = renderer->begin_content && cmark_isdigit((char)c) == 1; } else { (renderer->outc)(renderer, node, escape, c, nextc); renderer->begin_line = false; renderer->begin_content = renderer->begin_content && cmark_isdigit((char)c) == 1; } // If adding the character went beyond width, look for an // earlier place where the line could be broken: if (renderer->width > 0 && renderer->column > renderer->width && !renderer->begin_line && renderer->last_breakable > 0) { // copy from last_breakable to remainder cmark_chunk_set_cstr(renderer->mem, &remainder, (char *)renderer->buffer->ptr + renderer->last_breakable + 1); // truncate at last_breakable cmark_strbuf_truncate(renderer->buffer, renderer->last_breakable); // add newline, prefix, and remainder cmark_strbuf_putc(renderer->buffer, '\n'); cmark_strbuf_put(renderer->buffer, renderer->prefix->ptr, renderer->prefix->size); cmark_strbuf_put(renderer->buffer, remainder.data, remainder.len); renderer->column = renderer->prefix->size + remainder.len; cmark_chunk_free(renderer->mem, &remainder); renderer->last_breakable = 0; renderer->begin_line = false; renderer->begin_content = false; } i += len; } } // Assumes no newlines, assumes ascii content: void cmark_render_ascii(cmark_renderer *renderer, const char *s) { int origsize = renderer->buffer->size; cmark_strbuf_puts(renderer->buffer, s); renderer->column += renderer->buffer->size - origsize; } void cmark_render_code_point(cmark_renderer *renderer, uint32_t c) { cmark_utf8proc_encode_char(c, renderer->buffer); renderer->column += 1; } char *cmark_render(cmark_mem *mem, cmark_node *root, int options, int width, void (*outc)(cmark_renderer *, cmark_node *, cmark_escaping, int32_t, unsigned char), int (*render_node)(cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options)) { cmark_strbuf pref = CMARK_BUF_INIT(mem); cmark_strbuf buf = CMARK_BUF_INIT(mem); cmark_node *cur; cmark_event_type ev_type; char *result; cmark_iter *iter = cmark_iter_new(root); cmark_renderer renderer = {mem, &buf, &pref, 0, width, 0, 0, true, true, false, false, outc, S_cr, S_blankline, S_out, 0}; while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { cur = cmark_iter_get_node(iter); if (!render_node(&renderer, cur, ev_type, options)) { // a false value causes us to skip processing // the node's contents. this is used for // autolinks. cmark_iter_reset(iter, cur, CMARK_EVENT_EXIT); } } // ensure final newline if (renderer.buffer->size == 0 || renderer.buffer->ptr[renderer.buffer->size - 1] != '\n') { cmark_strbuf_putc(renderer.buffer, '\n'); } result = (char *)cmark_strbuf_detach(renderer.buffer); cmark_iter_free(iter); cmark_strbuf_free(renderer.prefix); cmark_strbuf_free(renderer.buffer); return result; } cmark-gfm-0.1.8/cbits/arena.c0000644000000000000000000000415513442034251014113 0ustar0000000000000000#include #include #include #include "cmark-gfm.h" #include "cmark-gfm-extension_api.h" static struct arena_chunk { size_t sz, used; uint8_t push_point; void *ptr; struct arena_chunk *prev; } *A = NULL; static struct arena_chunk *alloc_arena_chunk(size_t sz, struct arena_chunk *prev) { struct arena_chunk *c = (struct arena_chunk *)calloc(1, sizeof(*c)); if (!c) abort(); c->sz = sz; c->ptr = calloc(1, sz); if (!c->ptr) abort(); c->prev = prev; return c; } void cmark_arena_push(void) { if (!A) return; A->push_point = 1; A = alloc_arena_chunk(10240, A); } int cmark_arena_pop(void) { if (!A) return 0; while (A && !A->push_point) { free(A->ptr); struct arena_chunk *n = A->prev; free(A); A = n; } if (A) A->push_point = 0; return 1; } static void init_arena(void) { A = alloc_arena_chunk(4 * 1048576, NULL); } void cmark_arena_reset(void) { while (A) { free(A->ptr); struct arena_chunk *n = A->prev; free(A); A = n; } } static void *arena_calloc(size_t nmem, size_t size) { if (!A) init_arena(); size_t sz = nmem * size + sizeof(size_t); // Round allocation sizes to largest integer size to // ensure returned memory is correctly aligned const size_t align = sizeof(size_t) - 1; sz = (sz + align) & ~align; if (sz > A->sz) { A->prev = alloc_arena_chunk(sz, A->prev); return (uint8_t *) A->prev->ptr + sizeof(size_t); } if (sz > A->sz - A->used) { A = alloc_arena_chunk(A->sz + A->sz / 2, A); } void *ptr = (uint8_t *) A->ptr + A->used; A->used += sz; *((size_t *) ptr) = sz - sizeof(size_t); return (uint8_t *) ptr + sizeof(size_t); } static void *arena_realloc(void *ptr, size_t size) { if (!A) init_arena(); void *new_ptr = arena_calloc(1, size); if (ptr) memcpy(new_ptr, ptr, ((size_t *) ptr)[-1]); return new_ptr; } static void arena_free(void *ptr) { (void) ptr; /* no-op */ } cmark_mem CMARK_ARENA_MEM_ALLOCATOR = {arena_calloc, arena_realloc, arena_free}; cmark_mem *cmark_get_arena_mem_allocator() { return &CMARK_ARENA_MEM_ALLOCATOR; } cmark-gfm-0.1.8/cbits/linked_list.c0000644000000000000000000000140113442034251015315 0ustar0000000000000000#include #include "cmark-gfm.h" cmark_llist *cmark_llist_append(cmark_mem *mem, cmark_llist *head, void *data) { cmark_llist *tmp; cmark_llist *new_node = (cmark_llist *) mem->calloc(1, sizeof(cmark_llist)); new_node->data = data; new_node->next = NULL; if (!head) return new_node; for (tmp = head; tmp->next; tmp=tmp->next); tmp->next = new_node; return head; } void cmark_llist_free_full(cmark_mem *mem, cmark_llist *head, cmark_free_func free_func) { cmark_llist *tmp, *prev; for (tmp = head; tmp;) { if (free_func) free_func(mem, tmp->data); prev = tmp; tmp = tmp->next; mem->free(prev); } } void cmark_llist_free(cmark_mem *mem, cmark_llist *head) { cmark_llist_free_full(mem, head, NULL); } cmark-gfm-0.1.8/cbits/plaintext.c0000644000000000000000000001447013442037162015042 0ustar0000000000000000#include "node.h" #include "syntax_extension.h" #include "render.h" #define OUT(s, wrap, escaping) renderer->out(renderer, node, s, wrap, escaping) #define LIT(s) renderer->out(renderer, node, s, false, LITERAL) #define CR() renderer->cr(renderer) #define BLANKLINE() renderer->blankline(renderer) #define LISTMARKER_SIZE 20 // Functions to convert cmark_nodes to plain text strings. static CMARK_INLINE void outc(cmark_renderer *renderer, cmark_node *node, cmark_escaping escape, int32_t c, unsigned char nextc) { cmark_render_code_point(renderer, c); } // if node is a block node, returns node. // otherwise returns first block-level node that is an ancestor of node. // if there is no block-level ancestor, returns NULL. static cmark_node *get_containing_block(cmark_node *node) { while (node) { if (CMARK_NODE_BLOCK_P(node)) { return node; } else { node = node->parent; } } return NULL; } static int S_render_node(cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { cmark_node *tmp; int list_number; cmark_delim_type list_delim; int i; bool entering = (ev_type == CMARK_EVENT_ENTER); char listmarker[LISTMARKER_SIZE]; bool first_in_list_item; bufsize_t marker_width; bool allow_wrap = renderer->width > 0 && !(CMARK_OPT_NOBREAKS & options) && !(CMARK_OPT_HARDBREAKS & options); // Don't adjust tight list status til we've started the list. // Otherwise we loose the blank line between a paragraph and // a following list. if (!(node->type == CMARK_NODE_ITEM && node->prev == NULL && entering)) { tmp = get_containing_block(node); renderer->in_tight_list_item = tmp && // tmp might be NULL if there is no containing block ((tmp->type == CMARK_NODE_ITEM && cmark_node_get_list_tight(tmp->parent)) || (tmp && tmp->parent && tmp->parent->type == CMARK_NODE_ITEM && cmark_node_get_list_tight(tmp->parent->parent))); } if (node->extension && node->extension->plaintext_render_func) { node->extension->plaintext_render_func(node->extension, renderer, node, ev_type, options); return 1; } switch (node->type) { case CMARK_NODE_DOCUMENT: break; case CMARK_NODE_BLOCK_QUOTE: break; case CMARK_NODE_LIST: if (!entering && node->next && (node->next->type == CMARK_NODE_CODE_BLOCK || node->next->type == CMARK_NODE_LIST)) { CR(); } break; case CMARK_NODE_ITEM: if (cmark_node_get_list_type(node->parent) == CMARK_BULLET_LIST) { marker_width = 4; } else { list_number = cmark_node_get_list_start(node->parent); list_delim = cmark_node_get_list_delim(node->parent); tmp = node; while (tmp->prev) { tmp = tmp->prev; list_number += 1; } // we ensure a width of at least 4 so // we get nice transition from single digits // to double snprintf(listmarker, LISTMARKER_SIZE, "%d%s%s", list_number, list_delim == CMARK_PAREN_DELIM ? ")" : ".", list_number < 10 ? " " : " "); marker_width = (bufsize_t)strlen(listmarker); } if (entering) { if (cmark_node_get_list_type(node->parent) == CMARK_BULLET_LIST) { LIT(" - "); renderer->begin_content = true; } else { LIT(listmarker); renderer->begin_content = true; } for (i = marker_width; i--;) { cmark_strbuf_putc(renderer->prefix, ' '); } } else { cmark_strbuf_truncate(renderer->prefix, renderer->prefix->size - marker_width); CR(); } break; case CMARK_NODE_HEADING: if (entering) { renderer->begin_content = true; renderer->no_linebreaks = true; } else { renderer->no_linebreaks = false; BLANKLINE(); } break; case CMARK_NODE_CODE_BLOCK: first_in_list_item = node->prev == NULL && node->parent && node->parent->type == CMARK_NODE_ITEM; if (!first_in_list_item) { BLANKLINE(); } OUT(cmark_node_get_literal(node), false, LITERAL); BLANKLINE(); break; case CMARK_NODE_HTML_BLOCK: break; case CMARK_NODE_CUSTOM_BLOCK: break; case CMARK_NODE_THEMATIC_BREAK: BLANKLINE(); break; case CMARK_NODE_PARAGRAPH: if (!entering) { BLANKLINE(); } break; case CMARK_NODE_TEXT: OUT(cmark_node_get_literal(node), allow_wrap, NORMAL); break; case CMARK_NODE_LINEBREAK: CR(); break; case CMARK_NODE_SOFTBREAK: if (CMARK_OPT_HARDBREAKS & options) { CR(); } else if (!renderer->no_linebreaks && renderer->width == 0 && !(CMARK_OPT_HARDBREAKS & options) && !(CMARK_OPT_NOBREAKS & options)) { CR(); } else { OUT(" ", allow_wrap, LITERAL); } break; case CMARK_NODE_CODE: OUT(cmark_node_get_literal(node), allow_wrap, LITERAL); break; case CMARK_NODE_HTML_INLINE: break; case CMARK_NODE_CUSTOM_INLINE: break; case CMARK_NODE_STRONG: break; case CMARK_NODE_EMPH: break; case CMARK_NODE_LINK: break; case CMARK_NODE_IMAGE: break; case CMARK_NODE_FOOTNOTE_REFERENCE: if (entering) { LIT("[^"); OUT(cmark_chunk_to_cstr(renderer->mem, &node->as.literal), false, LITERAL); LIT("]"); } break; case CMARK_NODE_FOOTNOTE_DEFINITION: if (entering) { renderer->footnote_ix += 1; LIT("[^"); char n[32]; snprintf(n, sizeof(n), "%d", renderer->footnote_ix); OUT(n, false, LITERAL); LIT("]: "); cmark_strbuf_puts(renderer->prefix, " "); } else { cmark_strbuf_truncate(renderer->prefix, renderer->prefix->size - 4); } break; default: assert(false); break; } return 1; } char *cmark_render_plaintext(cmark_node *root, int options, int width) { return cmark_render_plaintext_with_mem(root, options, width, cmark_node_mem(root)); } char *cmark_render_plaintext_with_mem(cmark_node *root, int options, int width, cmark_mem *mem) { if (options & CMARK_OPT_HARDBREAKS) { // disable breaking on width, since it has // a different meaning with OPT_HARDBREAKS width = 0; } return cmark_render(mem, root, options, width, outc, S_render_node); } cmark-gfm-0.1.8/cbits/plugin.c0000644000000000000000000000176013442034251014322 0ustar0000000000000000#include #include "plugin.h" extern cmark_mem CMARK_DEFAULT_MEM_ALLOCATOR; int cmark_plugin_register_syntax_extension(cmark_plugin * plugin, cmark_syntax_extension * extension) { plugin->syntax_extensions = cmark_llist_append(&CMARK_DEFAULT_MEM_ALLOCATOR, plugin->syntax_extensions, extension); return 1; } cmark_plugin * cmark_plugin_new(void) { cmark_plugin *res = (cmark_plugin *) CMARK_DEFAULT_MEM_ALLOCATOR.calloc(1, sizeof(cmark_plugin)); res->syntax_extensions = NULL; return res; } void cmark_plugin_free(cmark_plugin *plugin) { cmark_llist_free_full(&CMARK_DEFAULT_MEM_ALLOCATOR, plugin->syntax_extensions, (cmark_free_func) cmark_syntax_extension_free); CMARK_DEFAULT_MEM_ALLOCATOR.free(plugin); } cmark_llist * cmark_plugin_steal_syntax_extensions(cmark_plugin *plugin) { cmark_llist *res = plugin->syntax_extensions; plugin->syntax_extensions = NULL; return res; } cmark-gfm-0.1.8/cbits/registry.c0000644000000000000000000000307613442034251014676 0ustar0000000000000000#include #include #include #include "config.h" #include "cmark-gfm.h" #include "syntax_extension.h" #include "registry.h" #include "plugin.h" extern cmark_mem CMARK_DEFAULT_MEM_ALLOCATOR; static cmark_llist *syntax_extensions = NULL; void cmark_register_plugin(cmark_plugin_init_func reg_fn) { cmark_plugin *plugin = cmark_plugin_new(); if (!reg_fn(plugin)) { cmark_plugin_free(plugin); return; } cmark_llist *syntax_extensions_list = cmark_plugin_steal_syntax_extensions(plugin), *it; for (it = syntax_extensions_list; it; it = it->next) { syntax_extensions = cmark_llist_append(&CMARK_DEFAULT_MEM_ALLOCATOR, syntax_extensions, it->data); } cmark_llist_free(&CMARK_DEFAULT_MEM_ALLOCATOR, syntax_extensions_list); cmark_plugin_free(plugin); } void cmark_release_plugins(void) { if (syntax_extensions) { cmark_llist_free_full( &CMARK_DEFAULT_MEM_ALLOCATOR, syntax_extensions, (cmark_free_func) cmark_syntax_extension_free); syntax_extensions = NULL; } } cmark_llist *cmark_list_syntax_extensions(cmark_mem *mem) { cmark_llist *it; cmark_llist *res = NULL; for (it = syntax_extensions; it; it = it->next) { res = cmark_llist_append(mem, res, it->data); } return res; } cmark_syntax_extension *cmark_find_syntax_extension(const char *name) { cmark_llist *tmp; for (tmp = syntax_extensions; tmp; tmp = tmp->next) { cmark_syntax_extension *ext = (cmark_syntax_extension *) tmp->data; if (!strcmp(ext->name, name)) return ext; } return NULL; } cmark-gfm-0.1.8/cbits/syntax_extension.c0000644000000000000000000001315213442034251016444 0ustar0000000000000000#include #include #include "cmark-gfm.h" #include "syntax_extension.h" #include "buffer.h" extern cmark_mem CMARK_DEFAULT_MEM_ALLOCATOR; static cmark_mem *_mem = &CMARK_DEFAULT_MEM_ALLOCATOR; void cmark_syntax_extension_free(cmark_mem *mem, cmark_syntax_extension *extension) { if (extension->free_function && extension->priv) { extension->free_function(mem, extension->priv); } cmark_llist_free(mem, extension->special_inline_chars); mem->free(extension->name); mem->free(extension); } cmark_syntax_extension *cmark_syntax_extension_new(const char *name) { cmark_syntax_extension *res = (cmark_syntax_extension *) _mem->calloc(1, sizeof(cmark_syntax_extension)); res->name = (char *) _mem->calloc(1, sizeof(char) * (strlen(name)) + 1); strcpy(res->name, name); return res; } cmark_node_type cmark_syntax_extension_add_node(int is_inline) { cmark_node_type *ref = !is_inline ? &CMARK_NODE_LAST_BLOCK : &CMARK_NODE_LAST_INLINE; if ((*ref & CMARK_NODE_VALUE_MASK) == CMARK_NODE_VALUE_MASK) { assert(false); return (cmark_node_type) 0; } return *ref = (cmark_node_type) ((int) *ref + 1); } void cmark_syntax_extension_set_emphasis(cmark_syntax_extension *extension, int emphasis) { extension->emphasis = emphasis == 1; } void cmark_syntax_extension_set_open_block_func(cmark_syntax_extension *extension, cmark_open_block_func func) { extension->try_opening_block = func; } void cmark_syntax_extension_set_match_block_func(cmark_syntax_extension *extension, cmark_match_block_func func) { extension->last_block_matches = func; } void cmark_syntax_extension_set_match_inline_func(cmark_syntax_extension *extension, cmark_match_inline_func func) { extension->match_inline = func; } void cmark_syntax_extension_set_inline_from_delim_func(cmark_syntax_extension *extension, cmark_inline_from_delim_func func) { extension->insert_inline_from_delim = func; } void cmark_syntax_extension_set_special_inline_chars(cmark_syntax_extension *extension, cmark_llist *special_chars) { extension->special_inline_chars = special_chars; } void cmark_syntax_extension_set_get_type_string_func(cmark_syntax_extension *extension, cmark_get_type_string_func func) { extension->get_type_string_func = func; } void cmark_syntax_extension_set_can_contain_func(cmark_syntax_extension *extension, cmark_can_contain_func func) { extension->can_contain_func = func; } void cmark_syntax_extension_set_contains_inlines_func(cmark_syntax_extension *extension, cmark_contains_inlines_func func) { extension->contains_inlines_func = func; } void cmark_syntax_extension_set_commonmark_render_func(cmark_syntax_extension *extension, cmark_common_render_func func) { extension->commonmark_render_func = func; } void cmark_syntax_extension_set_plaintext_render_func(cmark_syntax_extension *extension, cmark_common_render_func func) { extension->plaintext_render_func = func; } void cmark_syntax_extension_set_latex_render_func(cmark_syntax_extension *extension, cmark_common_render_func func) { extension->latex_render_func = func; } void cmark_syntax_extension_set_xml_attr_func(cmark_syntax_extension *extension, cmark_xml_attr_func func) { extension->xml_attr_func = func; } void cmark_syntax_extension_set_man_render_func(cmark_syntax_extension *extension, cmark_common_render_func func) { extension->man_render_func = func; } void cmark_syntax_extension_set_html_render_func(cmark_syntax_extension *extension, cmark_html_render_func func) { extension->html_render_func = func; } void cmark_syntax_extension_set_html_filter_func(cmark_syntax_extension *extension, cmark_html_filter_func func) { extension->html_filter_func = func; } void cmark_syntax_extension_set_postprocess_func(cmark_syntax_extension *extension, cmark_postprocess_func func) { extension->postprocess_func = func; } void cmark_syntax_extension_set_private(cmark_syntax_extension *extension, void *priv, cmark_free_func free_func) { extension->priv = priv; extension->free_function = free_func; } void *cmark_syntax_extension_get_private(cmark_syntax_extension *extension) { return extension->priv; } void cmark_syntax_extension_set_opaque_alloc_func(cmark_syntax_extension *extension, cmark_opaque_alloc_func func) { extension->opaque_alloc_func = func; } void cmark_syntax_extension_set_opaque_free_func(cmark_syntax_extension *extension, cmark_opaque_free_func func) { extension->opaque_free_func = func; } void cmark_syntax_extension_set_commonmark_escape_func(cmark_syntax_extension *extension, cmark_commonmark_escape_func func) { extension->commonmark_escape_func = func; } cmark-gfm-0.1.8/cbits/autolink.c0000644000000000000000000002671013442037162014660 0ustar0000000000000000#include "autolink.h" #include #include #include #if defined(_WIN32) #define strncasecmp _strnicmp #else #include #endif static int is_valid_hostchar(const uint8_t *link, size_t link_len) { int32_t ch; int r = cmark_utf8proc_iterate(link, (bufsize_t)link_len, &ch); if (r < 0) return 0; return !cmark_utf8proc_is_space(ch) && !cmark_utf8proc_is_punctuation(ch); } static int sd_autolink_issafe(const uint8_t *link, size_t link_len) { static const size_t valid_uris_count = 3; static const char *valid_uris[] = {"http://", "https://", "ftp://"}; size_t i; for (i = 0; i < valid_uris_count; ++i) { size_t len = strlen(valid_uris[i]); if (link_len > len && strncasecmp((char *)link, valid_uris[i], len) == 0 && is_valid_hostchar(link + len, link_len - len)) return 1; } return 0; } static size_t autolink_delim(uint8_t *data, size_t link_end) { uint8_t cclose, copen; size_t i; for (i = 0; i < link_end; ++i) if (data[i] == '<') { link_end = i; break; } while (link_end > 0) { cclose = data[link_end - 1]; switch (cclose) { case ')': copen = '('; break; default: copen = 0; } if (strchr("?!.,:*_~'\"", data[link_end - 1]) != NULL) link_end--; else if (data[link_end - 1] == ';') { size_t new_end = link_end - 2; while (new_end > 0 && cmark_isalpha(data[new_end])) new_end--; if (new_end < link_end - 2 && data[new_end] == '&') link_end = new_end; else link_end--; } else if (copen != 0) { size_t closing = 0; size_t opening = 0; i = 0; /* Allow any number of matching brackets (as recognised in copen/cclose) * at the end of the URL. If there is a greater number of closing * brackets than opening ones, we remove one character from the end of * the link. * * Examples (input text => output linked portion): * * http://www.pokemon.com/Pikachu_(Electric) * => http://www.pokemon.com/Pikachu_(Electric) * * http://www.pokemon.com/Pikachu_((Electric) * => http://www.pokemon.com/Pikachu_((Electric) * * http://www.pokemon.com/Pikachu_(Electric)) * => http://www.pokemon.com/Pikachu_(Electric) * * http://www.pokemon.com/Pikachu_((Electric)) * => http://www.pokemon.com/Pikachu_((Electric)) */ while (i < link_end) { if (data[i] == copen) opening++; else if (data[i] == cclose) closing++; i++; } if (closing <= opening) break; link_end--; } else break; } return link_end; } static size_t check_domain(uint8_t *data, size_t size, int allow_short) { size_t i, np = 0, uscore1 = 0, uscore2 = 0; for (i = 1; i < size - 1; i++) { if (data[i] == '_') uscore2++; else if (data[i] == '.') { uscore1 = uscore2; uscore2 = 0; np++; } else if (!is_valid_hostchar(data + i, size - i) && data[i] != '-') break; } if (uscore1 > 0 || uscore2 > 0) return 0; if (allow_short) { /* We don't need a valid domain in the strict sense (with * least one dot; so just make sure it's composed of valid * domain characters and return the length of the the valid * sequence. */ return i; } else { /* a valid domain needs to have at least a dot. * that's as far as we get */ return np ? i : 0; } } static cmark_node *www_match(cmark_parser *parser, cmark_node *parent, cmark_inline_parser *inline_parser) { cmark_chunk *chunk = cmark_inline_parser_get_chunk(inline_parser); size_t max_rewind = cmark_inline_parser_get_offset(inline_parser); uint8_t *data = chunk->data + max_rewind; size_t size = chunk->len - max_rewind; int start = cmark_inline_parser_get_column(inline_parser); size_t link_end; if (max_rewind > 0 && strchr("*_~(", data[-1]) == NULL && !cmark_isspace(data[-1])) return 0; if (size < 4 || memcmp(data, "www.", strlen("www.")) != 0) return 0; link_end = check_domain(data, size, 0); if (link_end == 0) return NULL; while (link_end < size && !cmark_isspace(data[link_end])) link_end++; link_end = autolink_delim(data, link_end); if (link_end == 0) return NULL; cmark_inline_parser_set_offset(inline_parser, (int)(max_rewind + link_end)); cmark_node *node = cmark_node_new_with_mem(CMARK_NODE_LINK, parser->mem); cmark_strbuf buf; cmark_strbuf_init(parser->mem, &buf, 10); cmark_strbuf_puts(&buf, "http://"); cmark_strbuf_put(&buf, data, (bufsize_t)link_end); node->as.link.url = cmark_chunk_buf_detach(&buf); cmark_node *text = cmark_node_new_with_mem(CMARK_NODE_TEXT, parser->mem); text->as.literal = cmark_chunk_dup(chunk, (bufsize_t)max_rewind, (bufsize_t)link_end); cmark_node_append_child(node, text); node->start_line = text->start_line = node->end_line = text->end_line = cmark_inline_parser_get_line(inline_parser); node->start_column = text->start_column = start - 1; node->end_column = text->end_column = cmark_inline_parser_get_column(inline_parser) - 1; return node; } static cmark_node *url_match(cmark_parser *parser, cmark_node *parent, cmark_inline_parser *inline_parser) { size_t link_end, domain_len; int rewind = 0; cmark_chunk *chunk = cmark_inline_parser_get_chunk(inline_parser); int max_rewind = cmark_inline_parser_get_offset(inline_parser); uint8_t *data = chunk->data + max_rewind; size_t size = chunk->len - max_rewind; if (size < 4 || data[1] != '/' || data[2] != '/') return 0; while (rewind < max_rewind && cmark_isalpha(data[-rewind - 1])) rewind++; if (!sd_autolink_issafe(data - rewind, size + rewind)) return 0; link_end = strlen("://"); domain_len = check_domain(data + link_end, size - link_end, 1); if (domain_len == 0) return 0; link_end += domain_len; while (link_end < size && !cmark_isspace(data[link_end])) link_end++; link_end = autolink_delim(data, link_end); if (link_end == 0) return NULL; cmark_inline_parser_set_offset(inline_parser, (int)(max_rewind + link_end)); cmark_node_unput(parent, rewind); cmark_node *node = cmark_node_new_with_mem(CMARK_NODE_LINK, parser->mem); cmark_chunk url = cmark_chunk_dup(chunk, max_rewind - rewind, (bufsize_t)(link_end + rewind)); node->as.link.url = url; cmark_node *text = cmark_node_new_with_mem(CMARK_NODE_TEXT, parser->mem); text->as.literal = url; cmark_node_append_child(node, text); return node; } static cmark_node *match(cmark_syntax_extension *ext, cmark_parser *parser, cmark_node *parent, unsigned char c, cmark_inline_parser *inline_parser) { if (cmark_inline_parser_in_bracket(inline_parser, false) || cmark_inline_parser_in_bracket(inline_parser, true)) return NULL; if (c == ':') return url_match(parser, parent, inline_parser); if (c == 'w') return www_match(parser, parent, inline_parser); return NULL; // note that we could end up re-consuming something already a // part of an inline, because we don't track when the last // inline was finished in inlines.c. } static void postprocess_text(cmark_parser *parser, cmark_node *text, int offset, int depth) { // postprocess_text can recurse very deeply if there is a very long line of // '@' only. Stop at a reasonable depth to ensure it cannot crash. if (depth > 1000) return; size_t link_end; uint8_t *data = text->as.literal.data, *at; size_t size = text->as.literal.len; int rewind, max_rewind, nb = 0, np = 0, ns = 0; if (offset < 0 || (size_t)offset >= size) return; data += offset; size -= offset; at = (uint8_t *)memchr(data, '@', size); if (!at) return; max_rewind = (int)(at - data); data += max_rewind; size -= max_rewind; for (rewind = 0; rewind < max_rewind; ++rewind) { uint8_t c = data[-rewind - 1]; if (cmark_isalnum(c)) continue; if (strchr(".+-_", c) != NULL) continue; if (c == '/') ns++; break; } if (rewind == 0 || ns > 0) { postprocess_text(parser, text, max_rewind + 1 + offset, depth + 1); return; } for (link_end = 0; link_end < size; ++link_end) { uint8_t c = data[link_end]; if (cmark_isalnum(c)) continue; if (c == '@') nb++; else if (c == '.' && link_end < size - 1 && cmark_isalnum(data[link_end + 1])) np++; else if (c != '-' && c != '_') break; } if (link_end < 2 || nb != 1 || np == 0 || (!cmark_isalpha(data[link_end - 1]) && data[link_end - 1] != '.')) { postprocess_text(parser, text, max_rewind + 1 + offset, depth + 1); return; } link_end = autolink_delim(data, link_end); if (link_end == 0) { postprocess_text(parser, text, max_rewind + 1 + offset, depth + 1); return; } cmark_chunk_to_cstr(parser->mem, &text->as.literal); cmark_node *link_node = cmark_node_new_with_mem(CMARK_NODE_LINK, parser->mem); cmark_strbuf buf; cmark_strbuf_init(parser->mem, &buf, 10); cmark_strbuf_puts(&buf, "mailto:"); cmark_strbuf_put(&buf, data - rewind, (bufsize_t)(link_end + rewind)); link_node->as.link.url = cmark_chunk_buf_detach(&buf); cmark_node *link_text = cmark_node_new_with_mem(CMARK_NODE_TEXT, parser->mem); cmark_chunk email = cmark_chunk_dup( &text->as.literal, offset + max_rewind - rewind, (bufsize_t)(link_end + rewind)); cmark_chunk_to_cstr(parser->mem, &email); link_text->as.literal = email; cmark_node_append_child(link_node, link_text); cmark_node_insert_after(text, link_node); cmark_node *post = cmark_node_new_with_mem(CMARK_NODE_TEXT, parser->mem); post->as.literal = cmark_chunk_dup(&text->as.literal, (bufsize_t)(offset + max_rewind + link_end), (bufsize_t)(size - link_end)); cmark_chunk_to_cstr(parser->mem, &post->as.literal); cmark_node_insert_after(link_node, post); text->as.literal.len = offset + max_rewind - rewind; text->as.literal.data[text->as.literal.len] = 0; postprocess_text(parser, post, 0, depth + 1); } static cmark_node *postprocess(cmark_syntax_extension *ext, cmark_parser *parser, cmark_node *root) { cmark_iter *iter; cmark_event_type ev; cmark_node *node; bool in_link = false; cmark_consolidate_text_nodes(root); iter = cmark_iter_new(root); while ((ev = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { node = cmark_iter_get_node(iter); if (in_link) { if (ev == CMARK_EVENT_EXIT && node->type == CMARK_NODE_LINK) { in_link = false; } continue; } if (ev == CMARK_EVENT_ENTER && node->type == CMARK_NODE_LINK) { in_link = true; continue; } if (ev == CMARK_EVENT_ENTER && node->type == CMARK_NODE_TEXT) { postprocess_text(parser, node, 0, /*depth*/0); } } cmark_iter_free(iter); return root; } cmark_syntax_extension *create_autolink_extension(void) { cmark_syntax_extension *ext = cmark_syntax_extension_new("autolink"); cmark_llist *special_chars = NULL; cmark_syntax_extension_set_match_inline_func(ext, match); cmark_syntax_extension_set_postprocess_func(ext, postprocess); cmark_mem *mem = cmark_get_default_mem_allocator(); special_chars = cmark_llist_append(mem, special_chars, (void *)':'); special_chars = cmark_llist_append(mem, special_chars, (void *)'w'); cmark_syntax_extension_set_special_inline_chars(ext, special_chars); return ext; } cmark-gfm-0.1.8/cbits/core-extensions.c0000644000000000000000000000161013442037162016147 0ustar0000000000000000#include "cmark-gfm-core-extensions.h" #include "autolink.h" #include "strikethrough.h" #include "table.h" #include "tagfilter.h" #include "tasklist.h" #include "registry.h" #include "plugin.h" static int core_extensions_registration(cmark_plugin *plugin) { cmark_plugin_register_syntax_extension(plugin, create_table_extension()); cmark_plugin_register_syntax_extension(plugin, create_strikethrough_extension()); cmark_plugin_register_syntax_extension(plugin, create_autolink_extension()); cmark_plugin_register_syntax_extension(plugin, create_tagfilter_extension()); cmark_plugin_register_syntax_extension(plugin, create_tasklist_extension()); return 1; } void cmark_gfm_core_extensions_ensure_registered(void) { static int registered = 0; if (!registered) { cmark_register_plugin(core_extensions_registration); registered = 1; } } cmark-gfm-0.1.8/cbits/ext_scanners.c0000644000000000000000000006206713442037162015533 0ustar0000000000000000/* Generated by re2c 1.1.1 */ #include "ext_scanners.h" #include bufsize_t _ext_scan_at(bufsize_t (*scanner)(const unsigned char *), unsigned char *ptr, int len, bufsize_t offset) { bufsize_t res; if (ptr == NULL || offset >= len) { return 0; } else { unsigned char lim = ptr[len]; ptr[len] = '\0'; res = scanner(ptr + offset); ptr[len] = lim; } return res; } bufsize_t _scan_table_start(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 64, 0, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *(marker = p); if (yych <= '{') { if (yych <= 0x1F) { if (yych <= '\t') { if (yych <= 0x08) goto yy3; goto yy4; } else { if (yych <= '\n') goto yy2; if (yych <= '\f') goto yy4; goto yy3; } } else { if (yych <= '-') { if (yych <= ' ') goto yy4; if (yych <= ',') goto yy3; goto yy5; } else { if (yych == ':') goto yy6; goto yy3; } } } else { if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '|') goto yy4; if (yych <= 0x7F) goto yy3; } else { if (yych <= 0xDF) goto yy7; if (yych <= 0xE0) goto yy9; goto yy10; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy11; if (yych <= 0xEF) goto yy10; goto yy12; } else { if (yych <= 0xF3) goto yy13; if (yych <= 0xF4) goto yy14; } } } yy2 : { return 0; } yy3: ++p; goto yy2; yy4: yych = *(marker = ++p); if (yybm[0 + yych] & 64) { goto yy15; } if (yych == '-') goto yy17; if (yych == ':') goto yy19; goto yy2; yy5: yych = *(marker = ++p); if (yybm[0 + yych] & 128) { goto yy17; } if (yych <= ' ') { if (yych <= 0x08) goto yy2; if (yych <= '\r') goto yy21; if (yych <= 0x1F) goto yy2; goto yy21; } else { if (yych <= ':') { if (yych <= '9') goto yy2; goto yy20; } else { if (yych == '|') goto yy21; goto yy2; } } yy6: yych = *(marker = ++p); if (yybm[0 + yych] & 128) { goto yy17; } goto yy2; yy7: yych = *++p; if (yych <= 0x7F) goto yy8; if (yych <= 0xBF) goto yy3; yy8: p = marker; goto yy2; yy9: yych = *++p; if (yych <= 0x9F) goto yy8; if (yych <= 0xBF) goto yy7; goto yy8; yy10: yych = *++p; if (yych <= 0x7F) goto yy8; if (yych <= 0xBF) goto yy7; goto yy8; yy11: yych = *++p; if (yych <= 0x7F) goto yy8; if (yych <= 0x9F) goto yy7; goto yy8; yy12: yych = *++p; if (yych <= 0x8F) goto yy8; if (yych <= 0xBF) goto yy10; goto yy8; yy13: yych = *++p; if (yych <= 0x7F) goto yy8; if (yych <= 0xBF) goto yy10; goto yy8; yy14: yych = *++p; if (yych <= 0x7F) goto yy8; if (yych <= 0x8F) goto yy10; goto yy8; yy15: yych = *++p; if (yybm[0 + yych] & 64) { goto yy15; } if (yych == '-') goto yy17; if (yych == ':') goto yy19; goto yy8; yy17: yych = *++p; if (yybm[0 + yych] & 128) { goto yy17; } if (yych <= 0x1F) { if (yych <= '\n') { if (yych <= 0x08) goto yy8; if (yych <= '\t') goto yy20; goto yy22; } else { if (yych <= '\f') goto yy20; if (yych <= '\r') goto yy24; goto yy8; } } else { if (yych <= ':') { if (yych <= ' ') goto yy20; if (yych <= '9') goto yy8; goto yy20; } else { if (yych == '|') goto yy25; goto yy8; } } yy19: yych = *++p; if (yybm[0 + yych] & 128) { goto yy17; } goto yy8; yy20: yych = *++p; yy21: if (yych <= '\r') { if (yych <= '\t') { if (yych <= 0x08) goto yy8; goto yy20; } else { if (yych <= '\n') goto yy22; if (yych <= '\f') goto yy20; goto yy24; } } else { if (yych <= ' ') { if (yych <= 0x1F) goto yy8; goto yy20; } else { if (yych == '|') goto yy25; goto yy8; } } yy22: ++p; { return (bufsize_t)(p - start); } yy24: yych = *++p; if (yych == '\n') goto yy22; goto yy8; yy25: yych = *++p; if (yybm[0 + yych] & 128) { goto yy17; } if (yych <= '\r') { if (yych <= '\t') { if (yych <= 0x08) goto yy8; goto yy25; } else { if (yych <= '\n') goto yy22; if (yych <= '\f') goto yy25; goto yy24; } } else { if (yych <= ' ') { if (yych <= 0x1F) goto yy8; goto yy25; } else { if (yych == ':') goto yy19; goto yy8; } } } } bufsize_t _scan_table_cell(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 0, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 128, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 64, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *(marker = p); if (yybm[0 + yych] & 64) { goto yy30; } if (yych <= 0xE0) { if (yych <= '\\') { if (yych <= '\n') goto yy29; if (yych <= '\r') goto yy32; goto yy34; } else { if (yych <= '|') goto yy32; if (yych <= 0xC1) goto yy29; if (yych <= 0xDF) goto yy36; goto yy38; } } else { if (yych <= 0xEF) { if (yych == 0xED) goto yy40; goto yy39; } else { if (yych <= 0xF0) goto yy41; if (yych <= 0xF3) goto yy42; if (yych <= 0xF4) goto yy43; } } yy29 : { return (bufsize_t)(p - start); } yy30: yych = *(marker = ++p); if (yybm[0 + yych] & 64) { goto yy30; } if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '\r') goto yy29; if (yych <= '\\') goto yy34; goto yy29; } else { if (yych <= 0xDF) goto yy36; if (yych <= 0xE0) goto yy38; goto yy39; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy40; if (yych <= 0xEF) goto yy39; goto yy41; } else { if (yych <= 0xF3) goto yy42; if (yych <= 0xF4) goto yy43; goto yy29; } } yy32: ++p; { return 0; } yy34: yych = *(marker = ++p); if (yybm[0 + yych] & 128) { goto yy34; } if (yych <= 0xDF) { if (yych <= '\f') { if (yych == '\n') goto yy29; goto yy30; } else { if (yych <= '\r') goto yy29; if (yych <= 0x7F) goto yy30; if (yych <= 0xC1) goto yy29; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy38; if (yych == 0xED) goto yy40; goto yy39; } else { if (yych <= 0xF0) goto yy41; if (yych <= 0xF3) goto yy42; if (yych <= 0xF4) goto yy43; goto yy29; } } yy36: yych = *++p; if (yych <= 0x7F) goto yy37; if (yych <= 0xBF) goto yy30; yy37: p = marker; goto yy29; yy38: yych = *++p; if (yych <= 0x9F) goto yy37; if (yych <= 0xBF) goto yy36; goto yy37; yy39: yych = *++p; if (yych <= 0x7F) goto yy37; if (yych <= 0xBF) goto yy36; goto yy37; yy40: yych = *++p; if (yych <= 0x7F) goto yy37; if (yych <= 0x9F) goto yy36; goto yy37; yy41: yych = *++p; if (yych <= 0x8F) goto yy37; if (yych <= 0xBF) goto yy39; goto yy37; yy42: yych = *++p; if (yych <= 0x7F) goto yy37; if (yych <= 0xBF) goto yy39; goto yy37; yy43: yych = *++p; if (yych <= 0x7F) goto yy37; if (yych <= 0x8F) goto yy39; goto yy37; } } bufsize_t _scan_table_cell_end(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; unsigned int yyaccept = 0; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *(marker = p); if (yych <= 0xDF) { if (yych <= '{') { if (yych != '\n') goto yy47; } else { if (yych <= '|') goto yy48; if (yych <= 0x7F) goto yy47; if (yych >= 0xC2) goto yy51; } } else { if (yych <= 0xEF) { if (yych <= 0xE0) goto yy53; if (yych == 0xED) goto yy55; goto yy54; } else { if (yych <= 0xF0) goto yy56; if (yych <= 0xF3) goto yy57; if (yych <= 0xF4) goto yy58; } } yy46 : { return 0; } yy47: ++p; goto yy46; yy48: yyaccept = 1; yych = *(marker = ++p); if (yybm[0 + yych] & 128) { goto yy48; } if (yych <= 0x08) goto yy50; if (yych <= '\n') goto yy59; if (yych <= '\r') goto yy60; yy50 : { return (bufsize_t)(p - start); } yy51: yych = *++p; if (yych <= 0x7F) goto yy52; if (yych <= 0xBF) goto yy47; yy52: p = marker; if (yyaccept == 0) { goto yy46; } else { goto yy50; } yy53: yych = *++p; if (yych <= 0x9F) goto yy52; if (yych <= 0xBF) goto yy51; goto yy52; yy54: yych = *++p; if (yych <= 0x7F) goto yy52; if (yych <= 0xBF) goto yy51; goto yy52; yy55: yych = *++p; if (yych <= 0x7F) goto yy52; if (yych <= 0x9F) goto yy51; goto yy52; yy56: yych = *++p; if (yych <= 0x8F) goto yy52; if (yych <= 0xBF) goto yy54; goto yy52; yy57: yych = *++p; if (yych <= 0x7F) goto yy52; if (yych <= 0xBF) goto yy54; goto yy52; yy58: yych = *++p; if (yych <= 0x7F) goto yy52; if (yych <= 0x8F) goto yy54; goto yy52; yy59: ++p; goto yy50; yy60: yych = *++p; if (yych == '\n') goto yy59; goto yy52; } } bufsize_t _scan_table_row_end(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *(marker = p); if (yych <= 0xC1) { if (yych <= '\f') { if (yych <= 0x08) goto yy64; if (yych == '\n') goto yy66; goto yy65; } else { if (yych <= 0x1F) { if (yych <= '\r') goto yy68; goto yy64; } else { if (yych <= ' ') goto yy65; if (yych <= 0x7F) goto yy64; } } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy69; if (yych <= 0xE0) goto yy71; if (yych <= 0xEC) goto yy72; goto yy73; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy72; goto yy74; } else { if (yych <= 0xF3) goto yy75; if (yych <= 0xF4) goto yy76; } } } yy63 : { return 0; } yy64: ++p; goto yy63; yy65: yych = *(marker = ++p); if (yych <= 0x08) goto yy63; if (yych <= '\r') goto yy78; if (yych == ' ') goto yy78; goto yy63; yy66: ++p; { return (bufsize_t)(p - start); } yy68: yych = *++p; if (yych == '\n') goto yy66; goto yy63; yy69: yych = *++p; if (yych <= 0x7F) goto yy70; if (yych <= 0xBF) goto yy64; yy70: p = marker; goto yy63; yy71: yych = *++p; if (yych <= 0x9F) goto yy70; if (yych <= 0xBF) goto yy69; goto yy70; yy72: yych = *++p; if (yych <= 0x7F) goto yy70; if (yych <= 0xBF) goto yy69; goto yy70; yy73: yych = *++p; if (yych <= 0x7F) goto yy70; if (yych <= 0x9F) goto yy69; goto yy70; yy74: yych = *++p; if (yych <= 0x8F) goto yy70; if (yych <= 0xBF) goto yy72; goto yy70; yy75: yych = *++p; if (yych <= 0x7F) goto yy70; if (yych <= 0xBF) goto yy72; goto yy70; yy76: yych = *++p; if (yych <= 0x7F) goto yy70; if (yych <= 0x8F) goto yy72; goto yy70; yy77: yych = *++p; yy78: if (yybm[0 + yych] & 128) { goto yy77; } if (yych <= 0x08) goto yy70; if (yych <= '\n') goto yy66; if (yych >= 0x0E) goto yy70; yych = *++p; if (yych == '\n') goto yy66; goto yy70; } } bufsize_t _scan_tasklist(const unsigned char *p) { const unsigned char *marker = NULL; const unsigned char *start = p; { unsigned char yych; static const unsigned char yybm[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 64, 0, 64, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 64, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 128, 128, 128, 128, 128, 128, 128, 128, 128, 128, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, }; yych = *(marker = p); if (yych <= '/') { if (yych <= 0x1F) { if (yych <= '\t') { if (yych <= 0x08) goto yy83; goto yy84; } else { if (yych <= '\n') goto yy82; if (yych <= '\f') goto yy84; goto yy83; } } else { if (yych <= '+') { if (yych <= ' ') goto yy84; if (yych <= ')') goto yy83; goto yy85; } else { if (yych == '-') goto yy85; goto yy83; } } } else { if (yych <= 0xEC) { if (yych <= 0xC1) { if (yych <= '9') goto yy86; if (yych <= 0x7F) goto yy83; } else { if (yych <= 0xDF) goto yy87; if (yych <= 0xE0) goto yy89; goto yy90; } } else { if (yych <= 0xF0) { if (yych <= 0xED) goto yy91; if (yych <= 0xEF) goto yy90; goto yy92; } else { if (yych <= 0xF3) goto yy93; if (yych <= 0xF4) goto yy94; } } } yy82 : { return 0; } yy83: ++p; goto yy82; yy84: yych = *(marker = ++p); if (yybm[0 + yych] & 64) { goto yy95; } if (yych <= ',') { if (yych <= ')') goto yy82; if (yych <= '+') goto yy97; goto yy82; } else { if (yych <= '-') goto yy97; if (yych <= '/') goto yy82; if (yych <= '9') goto yy98; goto yy82; } yy85: yych = *(marker = ++p); if (yych <= '\n') { if (yych == '\t') goto yy99; goto yy82; } else { if (yych <= '\f') goto yy99; if (yych == ' ') goto yy99; goto yy82; } yy86: yych = *(marker = ++p); if (yych <= 0x1F) { if (yych <= '\t') { if (yych <= 0x08) goto yy102; goto yy97; } else { if (yych <= '\n') goto yy82; if (yych <= '\f') goto yy97; goto yy102; } } else { if (yych <= 0x7F) { if (yych <= ' ') goto yy97; goto yy102; } else { if (yych <= 0xC1) goto yy82; if (yych <= 0xF4) goto yy102; goto yy82; } } yy87: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0xBF) goto yy83; yy88: p = marker; goto yy82; yy89: yych = *++p; if (yych <= 0x9F) goto yy88; if (yych <= 0xBF) goto yy87; goto yy88; yy90: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0xBF) goto yy87; goto yy88; yy91: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0x9F) goto yy87; goto yy88; yy92: yych = *++p; if (yych <= 0x8F) goto yy88; if (yych <= 0xBF) goto yy90; goto yy88; yy93: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0xBF) goto yy90; goto yy88; yy94: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0x8F) goto yy90; goto yy88; yy95: yych = *++p; if (yybm[0 + yych] & 64) { goto yy95; } if (yych <= ',') { if (yych <= ')') goto yy88; if (yych >= ',') goto yy88; } else { if (yych <= '-') goto yy97; if (yych <= '/') goto yy88; if (yych <= '9') goto yy98; goto yy88; } yy97: yych = *++p; if (yych == '[') goto yy88; goto yy100; yy98: yych = *++p; if (yych <= '\n') { if (yych == '\t') goto yy97; goto yy102; } else { if (yych <= '\f') goto yy97; if (yych == ' ') goto yy97; goto yy102; } yy99: yych = *++p; yy100: if (yych <= '\f') { if (yych == '\t') goto yy99; if (yych <= '\n') goto yy88; goto yy99; } else { if (yych <= ' ') { if (yych <= 0x1F) goto yy88; goto yy99; } else { if (yych == '[') goto yy110; goto yy88; } } yy101: yych = *++p; yy102: if (yybm[0 + yych] & 128) { goto yy101; } if (yych <= 0xC1) { if (yych <= '\f') { if (yych <= 0x08) goto yy97; if (yych == '\n') goto yy88; goto yy99; } else { if (yych == ' ') goto yy99; if (yych <= 0x7F) goto yy97; goto yy88; } } else { if (yych <= 0xED) { if (yych <= 0xDF) goto yy103; if (yych <= 0xE0) goto yy104; if (yych <= 0xEC) goto yy105; goto yy106; } else { if (yych <= 0xF0) { if (yych <= 0xEF) goto yy105; goto yy107; } else { if (yych <= 0xF3) goto yy108; if (yych <= 0xF4) goto yy109; goto yy88; } } } yy103: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0xBF) goto yy97; goto yy88; yy104: yych = *++p; if (yych <= 0x9F) goto yy88; if (yych <= 0xBF) goto yy103; goto yy88; yy105: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0xBF) goto yy103; goto yy88; yy106: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0x9F) goto yy103; goto yy88; yy107: yych = *++p; if (yych <= 0x8F) goto yy88; if (yych <= 0xBF) goto yy105; goto yy88; yy108: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0xBF) goto yy105; goto yy88; yy109: yych = *++p; if (yych <= 0x7F) goto yy88; if (yych <= 0x8F) goto yy105; goto yy88; yy110: yych = *++p; if (yych <= 'W') { if (yych != ' ') goto yy88; } else { if (yych <= 'X') goto yy111; if (yych != 'x') goto yy88; } yy111: yych = *++p; if (yych != ']') goto yy88; yych = *++p; if (yych <= '\n') { if (yych != '\t') goto yy88; } else { if (yych <= '\f') goto yy113; if (yych != ' ') goto yy88; } yy113: yych = *++p; if (yych <= '\n') { if (yych == '\t') goto yy113; } else { if (yych <= '\f') goto yy113; if (yych == ' ') goto yy113; } { return (bufsize_t)(p - start); } } } cmark-gfm-0.1.8/cbits/strikethrough.c0000644000000000000000000001333713442034251015731 0ustar0000000000000000#include "strikethrough.h" #include #include cmark_node_type CMARK_NODE_STRIKETHROUGH; static cmark_node *match(cmark_syntax_extension *self, cmark_parser *parser, cmark_node *parent, unsigned char character, cmark_inline_parser *inline_parser) { cmark_node *res = NULL; int left_flanking, right_flanking, punct_before, punct_after, delims; char buffer[101]; if (character != '~') return NULL; delims = cmark_inline_parser_scan_delimiters( inline_parser, sizeof(buffer) - 1, '~', &left_flanking, &right_flanking, &punct_before, &punct_after); memset(buffer, '~', delims); buffer[delims] = 0; res = cmark_node_new_with_mem(CMARK_NODE_TEXT, parser->mem); cmark_node_set_literal(res, buffer); res->start_line = res->end_line = cmark_inline_parser_get_line(inline_parser); res->start_column = cmark_inline_parser_get_column(inline_parser) - delims; if ((left_flanking || right_flanking) && (delims == 2 || (!(parser->options & CMARK_OPT_STRIKETHROUGH_DOUBLE_TILDE) && delims == 1))) { cmark_inline_parser_push_delimiter(inline_parser, character, left_flanking, right_flanking, res); } return res; } static delimiter *insert(cmark_syntax_extension *self, cmark_parser *parser, cmark_inline_parser *inline_parser, delimiter *opener, delimiter *closer) { cmark_node *strikethrough; cmark_node *tmp, *next; delimiter *delim, *tmp_delim; delimiter *res = closer->next; strikethrough = opener->inl_text; if (opener->inl_text->as.literal.len != closer->inl_text->as.literal.len) goto done; if (!cmark_node_set_type(strikethrough, CMARK_NODE_STRIKETHROUGH)) goto done; cmark_node_set_syntax_extension(strikethrough, self); tmp = cmark_node_next(opener->inl_text); while (tmp) { if (tmp == closer->inl_text) break; next = cmark_node_next(tmp); cmark_node_append_child(strikethrough, tmp); tmp = next; } strikethrough->end_column = closer->inl_text->start_column + closer->inl_text->as.literal.len - 1; cmark_node_free(closer->inl_text); delim = closer; while (delim != NULL && delim != opener) { tmp_delim = delim->previous; cmark_inline_parser_remove_delimiter(inline_parser, delim); delim = tmp_delim; } cmark_inline_parser_remove_delimiter(inline_parser, opener); done: return res; } static const char *get_type_string(cmark_syntax_extension *extension, cmark_node *node) { return node->type == CMARK_NODE_STRIKETHROUGH ? "strikethrough" : ""; } static int can_contain(cmark_syntax_extension *extension, cmark_node *node, cmark_node_type child_type) { if (node->type != CMARK_NODE_STRIKETHROUGH) return false; return CMARK_NODE_TYPE_INLINE_P(child_type); } static void commonmark_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { renderer->out(renderer, node, "~~", false, LITERAL); } static void latex_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { // requires \usepackage{ulem} bool entering = (ev_type == CMARK_EVENT_ENTER); if (entering) { renderer->out(renderer, node, "\\sout{", false, LITERAL); } else { renderer->out(renderer, node, "}", false, LITERAL); } } static void man_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); if (entering) { renderer->cr(renderer); renderer->out(renderer, node, ".ST \"", false, LITERAL); } else { renderer->out(renderer, node, "\"", false, LITERAL); renderer->cr(renderer); } } static void html_render(cmark_syntax_extension *extension, cmark_html_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); if (entering) { cmark_strbuf_puts(renderer->html, ""); } else { cmark_strbuf_puts(renderer->html, ""); } } static void plaintext_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { renderer->out(renderer, node, "~", false, LITERAL); } cmark_syntax_extension *create_strikethrough_extension(void) { cmark_syntax_extension *ext = cmark_syntax_extension_new("strikethrough"); cmark_llist *special_chars = NULL; cmark_syntax_extension_set_get_type_string_func(ext, get_type_string); cmark_syntax_extension_set_can_contain_func(ext, can_contain); cmark_syntax_extension_set_commonmark_render_func(ext, commonmark_render); cmark_syntax_extension_set_latex_render_func(ext, latex_render); cmark_syntax_extension_set_man_render_func(ext, man_render); cmark_syntax_extension_set_html_render_func(ext, html_render); cmark_syntax_extension_set_plaintext_render_func(ext, plaintext_render); CMARK_NODE_STRIKETHROUGH = cmark_syntax_extension_add_node(1); cmark_syntax_extension_set_match_inline_func(ext, match); cmark_syntax_extension_set_inline_from_delim_func(ext, insert); cmark_mem *mem = cmark_get_default_mem_allocator(); special_chars = cmark_llist_append(mem, special_chars, (void *)'~'); cmark_syntax_extension_set_special_inline_chars(ext, special_chars); cmark_syntax_extension_set_emphasis(ext, 1); return ext; } cmark-gfm-0.1.8/cbits/table.c0000644000000000000000000006134613442037162014125 0ustar0000000000000000#include #include #include #include #include #include #include #include "ext_scanners.h" #include "strikethrough.h" #include "table.h" #include "cmark-gfm-core-extensions.h" cmark_node_type CMARK_NODE_TABLE, CMARK_NODE_TABLE_ROW, CMARK_NODE_TABLE_CELL; typedef struct { uint16_t n_columns; cmark_llist *cells; } table_row; typedef struct { uint16_t n_columns; uint8_t *alignments; } node_table; typedef struct { bool is_header; } node_table_row; typedef struct { cmark_strbuf *buf; int start_offset, end_offset, internal_offset; } node_cell; static void free_table_cell(cmark_mem *mem, void *data) { node_cell *cell = (node_cell *)data; cmark_strbuf_free((cmark_strbuf *)cell->buf); mem->free(cell->buf); mem->free(cell); } static void free_table_row(cmark_mem *mem, table_row *row) { if (!row) return; cmark_llist_free_full(mem, row->cells, (cmark_free_func)free_table_cell); mem->free(row); } static void free_node_table(cmark_mem *mem, void *ptr) { node_table *t = (node_table *)ptr; mem->free(t->alignments); mem->free(t); } static void free_node_table_row(cmark_mem *mem, void *ptr) { mem->free(ptr); } static int get_n_table_columns(cmark_node *node) { if (!node || node->type != CMARK_NODE_TABLE) return -1; return (int)((node_table *)node->as.opaque)->n_columns; } static int set_n_table_columns(cmark_node *node, uint16_t n_columns) { if (!node || node->type != CMARK_NODE_TABLE) return 0; ((node_table *)node->as.opaque)->n_columns = n_columns; return 1; } static uint8_t *get_table_alignments(cmark_node *node) { if (!node || node->type != CMARK_NODE_TABLE) return 0; return ((node_table *)node->as.opaque)->alignments; } static int set_table_alignments(cmark_node *node, uint8_t *alignments) { if (!node || node->type != CMARK_NODE_TABLE) return 0; ((node_table *)node->as.opaque)->alignments = alignments; return 1; } static cmark_strbuf *unescape_pipes(cmark_mem *mem, unsigned char *string, bufsize_t len) { cmark_strbuf *res = (cmark_strbuf *)mem->calloc(1, sizeof(cmark_strbuf)); bufsize_t r, w; cmark_strbuf_init(mem, res, len + 1); cmark_strbuf_put(res, string, len); cmark_strbuf_putc(res, '\0'); for (r = 0, w = 0; r < len; ++r) { if (res->ptr[r] == '\\' && res->ptr[r + 1] == '|') r++; res->ptr[w++] = res->ptr[r]; } cmark_strbuf_truncate(res, w); return res; } static table_row *row_from_string(cmark_syntax_extension *self, cmark_parser *parser, unsigned char *string, int len) { table_row *row = NULL; bufsize_t cell_matched = 1, pipe_matched = 1, offset; row = (table_row *)parser->mem->calloc(1, sizeof(table_row)); row->n_columns = 0; row->cells = NULL; offset = scan_table_cell_end(string, len, 0); // Parse the cells of the row. Stop if we reach the end of the input, or if we // cannot detect any more cells. while (offset < len && (cell_matched || pipe_matched)) { cell_matched = scan_table_cell(string, len, offset); pipe_matched = scan_table_cell_end(string, len, offset + cell_matched); if (cell_matched || pipe_matched) { cmark_strbuf *cell_buf = unescape_pipes(parser->mem, string + offset, cell_matched); cmark_strbuf_trim(cell_buf); node_cell *cell = (node_cell *)parser->mem->calloc(1, sizeof(*cell)); cell->buf = cell_buf; cell->start_offset = offset; cell->end_offset = offset + cell_matched - 1; while (cell->start_offset > 0 && string[cell->start_offset - 1] != '|') { --cell->start_offset; ++cell->internal_offset; } row->n_columns += 1; row->cells = cmark_llist_append(parser->mem, row->cells, cell); } offset += cell_matched + pipe_matched; if (!pipe_matched) { pipe_matched = scan_table_row_end(string, len, offset); offset += pipe_matched; } } if (offset != len || !row->n_columns) { free_table_row(parser->mem, row); row = NULL; } return row; } static cmark_node *try_opening_table_header(cmark_syntax_extension *self, cmark_parser *parser, cmark_node *parent_container, unsigned char *input, int len) { bufsize_t matched = scan_table_start(input, len, cmark_parser_get_first_nonspace(parser)); cmark_node *table_header; table_row *header_row = NULL; table_row *marker_row = NULL; node_table_row *ntr; const char *parent_string; uint16_t i; if (!matched) return parent_container; parent_string = cmark_node_get_string_content(parent_container); cmark_arena_push(); header_row = row_from_string(self, parser, (unsigned char *)parent_string, (int)strlen(parent_string)); if (!header_row) { free_table_row(parser->mem, header_row); cmark_arena_pop(); return parent_container; } marker_row = row_from_string(self, parser, input + cmark_parser_get_first_nonspace(parser), len - cmark_parser_get_first_nonspace(parser)); assert(marker_row); if (header_row->n_columns != marker_row->n_columns) { free_table_row(parser->mem, header_row); free_table_row(parser->mem, marker_row); cmark_arena_pop(); return parent_container; } if (cmark_arena_pop()) { header_row = row_from_string(self, parser, (unsigned char *)parent_string, (int)strlen(parent_string)); marker_row = row_from_string(self, parser, input + cmark_parser_get_first_nonspace(parser), len - cmark_parser_get_first_nonspace(parser)); } if (!cmark_node_set_type(parent_container, CMARK_NODE_TABLE)) { free_table_row(parser->mem, header_row); free_table_row(parser->mem, marker_row); return parent_container; } cmark_node_set_syntax_extension(parent_container, self); parent_container->as.opaque = parser->mem->calloc(1, sizeof(node_table)); set_n_table_columns(parent_container, header_row->n_columns); uint8_t *alignments = (uint8_t *)parser->mem->calloc(header_row->n_columns, sizeof(uint8_t)); cmark_llist *it = marker_row->cells; for (i = 0; it; it = it->next, ++i) { node_cell *node = (node_cell *)it->data; bool left = node->buf->ptr[0] == ':', right = node->buf->ptr[node->buf->size - 1] == ':'; if (left && right) alignments[i] = 'c'; else if (left) alignments[i] = 'l'; else if (right) alignments[i] = 'r'; } set_table_alignments(parent_container, alignments); table_header = cmark_parser_add_child(parser, parent_container, CMARK_NODE_TABLE_ROW, parent_container->start_column); cmark_node_set_syntax_extension(table_header, self); table_header->end_column = parent_container->start_column + (int)strlen(parent_string) - 2; table_header->start_line = table_header->end_line = parent_container->start_line; table_header->as.opaque = ntr = (node_table_row *)parser->mem->calloc(1, sizeof(node_table_row)); ntr->is_header = true; { cmark_llist *tmp; for (tmp = header_row->cells; tmp; tmp = tmp->next) { node_cell *cell = (node_cell *) tmp->data; cmark_node *header_cell = cmark_parser_add_child(parser, table_header, CMARK_NODE_TABLE_CELL, parent_container->start_column + cell->start_offset); header_cell->start_line = header_cell->end_line = parent_container->start_line; header_cell->internal_offset = cell->internal_offset; header_cell->end_column = parent_container->start_column + cell->end_offset; cmark_node_set_string_content(header_cell, (char *) cell->buf->ptr); cmark_node_set_syntax_extension(header_cell, self); } } cmark_parser_advance_offset( parser, (char *)input, (int)strlen((char *)input) - 1 - cmark_parser_get_offset(parser), false); free_table_row(parser->mem, header_row); free_table_row(parser->mem, marker_row); return parent_container; } static cmark_node *try_opening_table_row(cmark_syntax_extension *self, cmark_parser *parser, cmark_node *parent_container, unsigned char *input, int len) { cmark_node *table_row_block; table_row *row; if (cmark_parser_is_blank(parser)) return NULL; table_row_block = cmark_parser_add_child(parser, parent_container, CMARK_NODE_TABLE_ROW, parent_container->start_column); cmark_node_set_syntax_extension(table_row_block, self); table_row_block->end_column = parent_container->end_column; table_row_block->as.opaque = parser->mem->calloc(1, sizeof(node_table_row)); row = row_from_string(self, parser, input + cmark_parser_get_first_nonspace(parser), len - cmark_parser_get_first_nonspace(parser)); { cmark_llist *tmp; int i, table_columns = get_n_table_columns(parent_container); for (tmp = row->cells, i = 0; tmp && i < table_columns; tmp = tmp->next, ++i) { node_cell *cell = (node_cell *) tmp->data; cmark_node *node = cmark_parser_add_child(parser, table_row_block, CMARK_NODE_TABLE_CELL, parent_container->start_column + cell->start_offset); node->internal_offset = cell->internal_offset; node->end_column = parent_container->start_column + cell->end_offset; cmark_node_set_string_content(node, (char *) cell->buf->ptr); cmark_node_set_syntax_extension(node, self); } for (; i < table_columns; ++i) { cmark_node *node = cmark_parser_add_child( parser, table_row_block, CMARK_NODE_TABLE_CELL, 0); cmark_node_set_syntax_extension(node, self); } } free_table_row(parser->mem, row); cmark_parser_advance_offset(parser, (char *)input, len - 1 - cmark_parser_get_offset(parser), false); return table_row_block; } static cmark_node *try_opening_table_block(cmark_syntax_extension *self, int indented, cmark_parser *parser, cmark_node *parent_container, unsigned char *input, int len) { cmark_node_type parent_type = cmark_node_get_type(parent_container); if (!indented && parent_type == CMARK_NODE_PARAGRAPH) { return try_opening_table_header(self, parser, parent_container, input, len); } else if (!indented && parent_type == CMARK_NODE_TABLE) { return try_opening_table_row(self, parser, parent_container, input, len); } return NULL; } static int matches(cmark_syntax_extension *self, cmark_parser *parser, unsigned char *input, int len, cmark_node *parent_container) { int res = 0; if (cmark_node_get_type(parent_container) == CMARK_NODE_TABLE) { cmark_arena_push(); table_row *new_row = row_from_string( self, parser, input + cmark_parser_get_first_nonspace(parser), len - cmark_parser_get_first_nonspace(parser)); if (new_row && new_row->n_columns) res = 1; free_table_row(parser->mem, new_row); cmark_arena_pop(); } return res; } static const char *get_type_string(cmark_syntax_extension *self, cmark_node *node) { if (node->type == CMARK_NODE_TABLE) { return "table"; } else if (node->type == CMARK_NODE_TABLE_ROW) { if (((node_table_row *)node->as.opaque)->is_header) return "table_header"; else return "table_row"; } else if (node->type == CMARK_NODE_TABLE_CELL) { return "table_cell"; } return ""; } static int can_contain(cmark_syntax_extension *extension, cmark_node *node, cmark_node_type child_type) { if (node->type == CMARK_NODE_TABLE) { return child_type == CMARK_NODE_TABLE_ROW; } else if (node->type == CMARK_NODE_TABLE_ROW) { return child_type == CMARK_NODE_TABLE_CELL; } else if (node->type == CMARK_NODE_TABLE_CELL) { return child_type == CMARK_NODE_TEXT || child_type == CMARK_NODE_CODE || child_type == CMARK_NODE_EMPH || child_type == CMARK_NODE_STRONG || child_type == CMARK_NODE_LINK || child_type == CMARK_NODE_IMAGE || child_type == CMARK_NODE_STRIKETHROUGH || child_type == CMARK_NODE_HTML_INLINE || child_type == CMARK_NODE_FOOTNOTE_REFERENCE; } return false; } static int contains_inlines(cmark_syntax_extension *extension, cmark_node *node) { return node->type == CMARK_NODE_TABLE_CELL; } static void commonmark_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); if (node->type == CMARK_NODE_TABLE) { renderer->blankline(renderer); } else if (node->type == CMARK_NODE_TABLE_ROW) { if (entering) { renderer->cr(renderer); renderer->out(renderer, node, "|", false, LITERAL); } } else if (node->type == CMARK_NODE_TABLE_CELL) { if (entering) { renderer->out(renderer, node, " ", false, LITERAL); } else { renderer->out(renderer, node, " |", false, LITERAL); if (((node_table_row *)node->parent->as.opaque)->is_header && !node->next) { int i; uint8_t *alignments = get_table_alignments(node->parent->parent); uint16_t n_cols = ((node_table *)node->parent->parent->as.opaque)->n_columns; renderer->cr(renderer); renderer->out(renderer, node, "|", false, LITERAL); for (i = 0; i < n_cols; i++) { switch (alignments[i]) { case 0: renderer->out(renderer, node, " --- |", false, LITERAL); break; case 'l': renderer->out(renderer, node, " :-- |", false, LITERAL); break; case 'c': renderer->out(renderer, node, " :-: |", false, LITERAL); break; case 'r': renderer->out(renderer, node, " --: |", false, LITERAL); break; } } renderer->cr(renderer); } } } else { assert(false); } } static void latex_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); if (node->type == CMARK_NODE_TABLE) { if (entering) { int i; uint16_t n_cols; uint8_t *alignments = get_table_alignments(node); renderer->cr(renderer); renderer->out(renderer, node, "\\begin{table}", false, LITERAL); renderer->cr(renderer); renderer->out(renderer, node, "\\begin{tabular}{", false, LITERAL); n_cols = ((node_table *)node->as.opaque)->n_columns; for (i = 0; i < n_cols; i++) { switch(alignments[i]) { case 0: case 'l': renderer->out(renderer, node, "l", false, LITERAL); break; case 'c': renderer->out(renderer, node, "c", false, LITERAL); break; case 'r': renderer->out(renderer, node, "r", false, LITERAL); break; } } renderer->out(renderer, node, "}", false, LITERAL); renderer->cr(renderer); } else { renderer->out(renderer, node, "\\end{tabular}", false, LITERAL); renderer->cr(renderer); renderer->out(renderer, node, "\\end{table}", false, LITERAL); renderer->cr(renderer); } } else if (node->type == CMARK_NODE_TABLE_ROW) { if (!entering) { renderer->cr(renderer); } } else if (node->type == CMARK_NODE_TABLE_CELL) { if (!entering) { if (node->next) { renderer->out(renderer, node, " & ", false, LITERAL); } else { renderer->out(renderer, node, " \\\\", false, LITERAL); } } } else { assert(false); } } static const char *xml_attr(cmark_syntax_extension *extension, cmark_node *node) { if (node->type == CMARK_NODE_TABLE_CELL) { if (cmark_gfm_extensions_get_table_row_is_header(node->parent)) { uint8_t *alignments = get_table_alignments(node->parent->parent); int i = 0; cmark_node *n; for (n = node->parent->first_child; n; n = n->next, ++i) if (n == node) break; switch (alignments[i]) { case 'l': return " align=\"left\""; case 'c': return " align=\"center\""; case 'r': return " align=\"right\""; } } } return NULL; } static void man_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); if (node->type == CMARK_NODE_TABLE) { if (entering) { int i; uint16_t n_cols; uint8_t *alignments = get_table_alignments(node); renderer->cr(renderer); renderer->out(renderer, node, ".TS", false, LITERAL); renderer->cr(renderer); renderer->out(renderer, node, "tab(@);", false, LITERAL); renderer->cr(renderer); n_cols = ((node_table *)node->as.opaque)->n_columns; for (i = 0; i < n_cols; i++) { switch (alignments[i]) { case 'l': renderer->out(renderer, node, "l", false, LITERAL); break; case 0: case 'c': renderer->out(renderer, node, "c", false, LITERAL); break; case 'r': renderer->out(renderer, node, "r", false, LITERAL); break; } } if (n_cols) { renderer->out(renderer, node, ".", false, LITERAL); renderer->cr(renderer); } } else { renderer->out(renderer, node, ".TE", false, LITERAL); renderer->cr(renderer); } } else if (node->type == CMARK_NODE_TABLE_ROW) { if (!entering) { renderer->cr(renderer); } } else if (node->type == CMARK_NODE_TABLE_CELL) { if (!entering && node->next) { renderer->out(renderer, node, "@", false, LITERAL); } } else { assert(false); } } static void html_table_add_align(cmark_strbuf* html, const char* align, int options) { if (options & CMARK_OPT_TABLE_PREFER_STYLE_ATTRIBUTES) { cmark_strbuf_puts(html, " style=\"text-align: "); cmark_strbuf_puts(html, align); cmark_strbuf_puts(html, "\""); } else { cmark_strbuf_puts(html, " align=\""); cmark_strbuf_puts(html, align); cmark_strbuf_puts(html, "\""); } } struct html_table_state { unsigned need_closing_table_body : 1; unsigned in_table_header : 1; }; static void html_render(cmark_syntax_extension *extension, cmark_html_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); cmark_strbuf *html = renderer->html; cmark_node *n; // XXX: we just monopolise renderer->opaque. struct html_table_state *table_state = (struct html_table_state *)&renderer->opaque; if (node->type == CMARK_NODE_TABLE) { if (entering) { cmark_html_render_cr(html); cmark_strbuf_puts(html, "'); table_state->need_closing_table_body = false; } else { if (table_state->need_closing_table_body) { cmark_html_render_cr(html); cmark_strbuf_puts(html, ""); cmark_html_render_cr(html); } table_state->need_closing_table_body = false; cmark_html_render_cr(html); cmark_strbuf_puts(html, ""); cmark_html_render_cr(html); } } else if (node->type == CMARK_NODE_TABLE_ROW) { if (entering) { cmark_html_render_cr(html); if (((node_table_row *)node->as.opaque)->is_header) { table_state->in_table_header = 1; cmark_strbuf_puts(html, ""); cmark_html_render_cr(html); } else if (!table_state->need_closing_table_body) { cmark_strbuf_puts(html, ""); cmark_html_render_cr(html); table_state->need_closing_table_body = 1; } cmark_strbuf_puts(html, "'); } else { cmark_html_render_cr(html); cmark_strbuf_puts(html, ""); if (((node_table_row *)node->as.opaque)->is_header) { cmark_html_render_cr(html); cmark_strbuf_puts(html, ""); table_state->in_table_header = false; } } } else if (node->type == CMARK_NODE_TABLE_CELL) { uint8_t *alignments = get_table_alignments(node->parent->parent); if (entering) { cmark_html_render_cr(html); if (table_state->in_table_header) { cmark_strbuf_puts(html, "parent->first_child; n; n = n->next, ++i) if (n == node) break; switch (alignments[i]) { case 'l': html_table_add_align(html, "left", options); break; case 'c': html_table_add_align(html, "center", options); break; case 'r': html_table_add_align(html, "right", options); break; } cmark_html_render_sourcepos(node, html, options); cmark_strbuf_putc(html, '>'); } else { if (table_state->in_table_header) { cmark_strbuf_puts(html, ""); } else { cmark_strbuf_puts(html, ""); } } } else { assert(false); } } static void opaque_alloc(cmark_syntax_extension *self, cmark_mem *mem, cmark_node *node) { if (node->type == CMARK_NODE_TABLE) { node->as.opaque = mem->calloc(1, sizeof(node_table)); } else if (node->type == CMARK_NODE_TABLE_ROW) { node->as.opaque = mem->calloc(1, sizeof(node_table_row)); } else if (node->type == CMARK_NODE_TABLE_CELL) { node->as.opaque = mem->calloc(1, sizeof(node_cell)); } } static void opaque_free(cmark_syntax_extension *self, cmark_mem *mem, cmark_node *node) { if (node->type == CMARK_NODE_TABLE) { free_node_table(mem, node->as.opaque); } else if (node->type == CMARK_NODE_TABLE_ROW) { free_node_table_row(mem, node->as.opaque); } } static int escape(cmark_syntax_extension *self, cmark_node *node, int c) { return node->type != CMARK_NODE_TABLE && node->type != CMARK_NODE_TABLE_ROW && node->type != CMARK_NODE_TABLE_CELL && c == '|'; } cmark_syntax_extension *create_table_extension(void) { cmark_syntax_extension *self = cmark_syntax_extension_new("table"); cmark_syntax_extension_set_match_block_func(self, matches); cmark_syntax_extension_set_open_block_func(self, try_opening_table_block); cmark_syntax_extension_set_get_type_string_func(self, get_type_string); cmark_syntax_extension_set_can_contain_func(self, can_contain); cmark_syntax_extension_set_contains_inlines_func(self, contains_inlines); cmark_syntax_extension_set_commonmark_render_func(self, commonmark_render); cmark_syntax_extension_set_plaintext_render_func(self, commonmark_render); cmark_syntax_extension_set_latex_render_func(self, latex_render); cmark_syntax_extension_set_xml_attr_func(self, xml_attr); cmark_syntax_extension_set_man_render_func(self, man_render); cmark_syntax_extension_set_html_render_func(self, html_render); cmark_syntax_extension_set_opaque_alloc_func(self, opaque_alloc); cmark_syntax_extension_set_opaque_free_func(self, opaque_free); cmark_syntax_extension_set_commonmark_escape_func(self, escape); CMARK_NODE_TABLE = cmark_syntax_extension_add_node(0); CMARK_NODE_TABLE_ROW = cmark_syntax_extension_add_node(0); CMARK_NODE_TABLE_CELL = cmark_syntax_extension_add_node(0); return self; } uint16_t cmark_gfm_extensions_get_table_columns(cmark_node *node) { if (node->type != CMARK_NODE_TABLE) return 0; return ((node_table *)node->as.opaque)->n_columns; } uint8_t *cmark_gfm_extensions_get_table_alignments(cmark_node *node) { if (node->type != CMARK_NODE_TABLE) return 0; return ((node_table *)node->as.opaque)->alignments; } int cmark_gfm_extensions_set_table_columns(cmark_node *node, uint16_t n_columns) { return set_n_table_columns(node, n_columns); } int cmark_gfm_extensions_set_table_alignments(cmark_node *node, uint16_t ncols, uint8_t *alignments) { uint8_t *a = (uint8_t *)cmark_node_mem(node)->calloc(1, ncols); memcpy(a, alignments, ncols); return set_table_alignments(node, a); } int cmark_gfm_extensions_get_table_row_is_header(cmark_node *node) { if (!node || node->type != CMARK_NODE_TABLE_ROW) return 0; return ((node_table_row *)node->as.opaque)->is_header; } int cmark_gfm_extensions_set_table_row_is_header(cmark_node *node, int is_header) { if (!node || node->type != CMARK_NODE_TABLE_ROW) return 0; ((node_table_row *)node->as.opaque)->is_header = (is_header != 0); return 1; } cmark-gfm-0.1.8/cbits/tagfilter.c0000644000000000000000000000234213442034251015002 0ustar0000000000000000#include "tagfilter.h" #include #include static const char *blacklist[] = { "title", "textarea", "style", "xmp", "iframe", "noembed", "noframes", "script", "plaintext", NULL, }; static int is_tag(const unsigned char *tag_data, size_t tag_size, const char *tagname) { size_t i; if (tag_size < 3 || tag_data[0] != '<') return 0; i = 1; if (tag_data[i] == '/') { i++; } for (; i < tag_size; ++i, ++tagname) { if (*tagname == 0) break; if (tolower(tag_data[i]) != *tagname) return 0; } if (i == tag_size) return 0; if (cmark_isspace(tag_data[i]) || tag_data[i] == '>') return 1; if (tag_data[i] == '/' && tag_size >= i + 2 && tag_data[i + 1] == '>') return 1; return 0; } static int filter(cmark_syntax_extension *ext, const unsigned char *tag, size_t tag_len) { const char **it; for (it = blacklist; *it; ++it) { if (is_tag(tag, tag_len, *it)) { return 0; } } return 1; } cmark_syntax_extension *create_tagfilter_extension(void) { cmark_syntax_extension *ext = cmark_syntax_extension_new("tagfilter"); cmark_syntax_extension_set_html_filter_func(ext, filter); return ext; } cmark-gfm-0.1.8/cbits/tasklist.c0000644000000000000000000001135313442037162014665 0ustar0000000000000000#include "tasklist.h" #include #include #include #include "ext_scanners.h" typedef enum { CMARK_TASKLIST_NOCHECKED, CMARK_TASKLIST_CHECKED, } cmark_tasklist_type; static const char *get_type_string(cmark_syntax_extension *extension, cmark_node *node) { return "tasklist"; } char *cmark_gfm_extensions_get_tasklist_state(cmark_node *node) { if (!node || ((int)node->as.opaque != CMARK_TASKLIST_CHECKED && (int)node->as.opaque != CMARK_TASKLIST_NOCHECKED)) return 0; if ((int)node->as.opaque != CMARK_TASKLIST_CHECKED) { return "checked"; } else { return "unchecked"; } } static bool parse_node_item_prefix(cmark_parser *parser, const char *input, cmark_node *container) { bool res = false; if (parser->indent >= container->as.list.marker_offset + container->as.list.padding) { cmark_parser_advance_offset(parser, input, container->as.list.marker_offset + container->as.list.padding, true); res = true; } else if (parser->blank && container->first_child != NULL) { // if container->first_child is NULL, then the opening line // of the list item was blank after the list marker; in this // case, we are done with the list item. cmark_parser_advance_offset(parser, input, parser->first_nonspace - parser->offset, false); res = true; } return res; } static int matches(cmark_syntax_extension *self, cmark_parser *parser, unsigned char *input, int len, cmark_node *parent_container) { return parse_node_item_prefix(parser, (const char*)input, parent_container); } static int can_contain(cmark_syntax_extension *extension, cmark_node *node, cmark_node_type child_type) { return (node->type == CMARK_NODE_ITEM) ? 1 : 0; } static cmark_node *open_tasklist_item(cmark_syntax_extension *self, int indented, cmark_parser *parser, cmark_node *parent_container, unsigned char *input, int len) { cmark_node_type node_type = cmark_node_get_type(parent_container); if (node_type != CMARK_NODE_ITEM) { return NULL; } bufsize_t matched = scan_tasklist(input, len, 0); if (!matched) { return NULL; } cmark_node_set_syntax_extension(parent_container, self); cmark_parser_advance_offset(parser, (char *)input, 3, false); if (strstr((char*)input, "[x]")) { parent_container->as.opaque = (void *)CMARK_TASKLIST_CHECKED; } else { parent_container->as.opaque = (void *)CMARK_TASKLIST_NOCHECKED; } return NULL; } static void commonmark_render(cmark_syntax_extension *extension, cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); if (entering) { renderer->cr(renderer); if ((int)node->as.opaque == CMARK_TASKLIST_CHECKED) { renderer->out(renderer, node, "- [x] ", false, LITERAL); } else { renderer->out(renderer, node, "- [ ] ", false, LITERAL); } cmark_strbuf_puts(renderer->prefix, " "); } else { cmark_strbuf_truncate(renderer->prefix, renderer->prefix->size - 2); renderer->cr(renderer); } } static void html_render(cmark_syntax_extension *extension, cmark_html_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options) { bool entering = (ev_type == CMARK_EVENT_ENTER); if (entering) { cmark_html_render_cr(renderer->html); cmark_strbuf_puts(renderer->html, "html, options); cmark_strbuf_putc(renderer->html, '>'); if ((int)node->as.opaque == CMARK_TASKLIST_CHECKED) { cmark_strbuf_puts(renderer->html, " "); } else { cmark_strbuf_puts(renderer->html, " "); } } else { cmark_strbuf_puts(renderer->html, "\n"); } } cmark_syntax_extension *create_tasklist_extension(void) { cmark_syntax_extension *ext = cmark_syntax_extension_new("tasklist"); cmark_syntax_extension_set_match_block_func(ext, matches); cmark_syntax_extension_set_get_type_string_func(ext, get_type_string); cmark_syntax_extension_set_open_block_func(ext, open_tasklist_item); cmark_syntax_extension_set_can_contain_func(ext, can_contain); cmark_syntax_extension_set_commonmark_render_func(ext, commonmark_render); cmark_syntax_extension_set_plaintext_render_func(ext, commonmark_render); cmark_syntax_extension_set_html_render_func(ext, html_render); return ext; } cmark-gfm-0.1.8/cbits/footnotes.c0000644000000000000000000000176113442034251015045 0ustar0000000000000000#include "cmark-gfm.h" #include "parser.h" #include "footnotes.h" #include "inlines.h" #include "chunk.h" static void footnote_free(cmark_map *map, cmark_map_entry *_ref) { cmark_footnote *ref = (cmark_footnote *)_ref; cmark_mem *mem = map->mem; if (ref != NULL) { mem->free(ref->entry.label); if (ref->node) cmark_node_free(ref->node); mem->free(ref); } } void cmark_footnote_create(cmark_map *map, cmark_node *node) { cmark_footnote *ref; unsigned char *reflabel = normalize_map_label(map->mem, &node->as.literal); /* empty footnote name, or composed from only whitespace */ if (reflabel == NULL) return; assert(map->sorted == NULL); ref = (cmark_footnote *)map->mem->calloc(1, sizeof(*ref)); ref->entry.label = reflabel; ref->node = node; ref->entry.age = map->size; ref->entry.next = map->refs; map->refs = (cmark_map_entry *)ref; map->size++; } cmark_map *cmark_footnote_map_new(cmark_mem *mem) { return cmark_map_new(mem, footnote_free); } cmark-gfm-0.1.8/cbits/map.c0000644000000000000000000000547513442034251013610 0ustar0000000000000000#include "map.h" #include "utf8.h" #include "parser.h" // normalize map label: collapse internal whitespace to single space, // remove leading/trailing whitespace, case fold // Return NULL if the label is actually empty (i.e. composed solely from // whitespace) unsigned char *normalize_map_label(cmark_mem *mem, cmark_chunk *ref) { cmark_strbuf normalized = CMARK_BUF_INIT(mem); unsigned char *result; if (ref == NULL) return NULL; if (ref->len == 0) return NULL; cmark_utf8proc_case_fold(&normalized, ref->data, ref->len); cmark_strbuf_trim(&normalized); cmark_strbuf_normalize_whitespace(&normalized); result = cmark_strbuf_detach(&normalized); assert(result); if (result[0] == '\0') { mem->free(result); return NULL; } return result; } static int labelcmp(const unsigned char *a, const unsigned char *b) { return strcmp((const char *)a, (const char *)b); } static int refcmp(const void *p1, const void *p2) { cmark_map_entry *r1 = *(cmark_map_entry **)p1; cmark_map_entry *r2 = *(cmark_map_entry **)p2; int res = labelcmp(r1->label, r2->label); return res ? res : ((int)r1->age - (int)r2->age); } static int refsearch(const void *label, const void *p2) { cmark_map_entry *ref = *(cmark_map_entry **)p2; return labelcmp((const unsigned char *)label, ref->label); } static void sort_map(cmark_map *map) { unsigned int i = 0, last = 0, size = map->size; cmark_map_entry *r = map->refs, **sorted = NULL; sorted = (cmark_map_entry **)map->mem->calloc(size, sizeof(cmark_map_entry *)); while (r) { sorted[i++] = r; r = r->next; } qsort(sorted, size, sizeof(cmark_map_entry *), refcmp); for (i = 1; i < size; i++) { if (labelcmp(sorted[i]->label, sorted[last]->label) != 0) sorted[++last] = sorted[i]; } map->sorted = sorted; map->size = last + 1; } cmark_map_entry *cmark_map_lookup(cmark_map *map, cmark_chunk *label) { cmark_map_entry **ref = NULL; unsigned char *norm; if (label->len < 1 || label->len > MAX_LINK_LABEL_LENGTH) return NULL; if (map == NULL || !map->size) return NULL; norm = normalize_map_label(map->mem, label); if (norm == NULL) return NULL; if (!map->sorted) sort_map(map); ref = (cmark_map_entry **)bsearch(norm, map->sorted, map->size, sizeof(cmark_map_entry *), refsearch); map->mem->free(norm); if (!ref) return NULL; return ref[0]; } void cmark_map_free(cmark_map *map) { cmark_map_entry *ref; if (map == NULL) return; ref = map->refs; while (ref) { cmark_map_entry *next = ref->next; map->free(map, ref); ref = next; } map->mem->free(map->sorted); map->mem->free(map); } cmark_map *cmark_map_new(cmark_mem *mem, cmark_map_free_f free) { cmark_map *map = (cmark_map *)mem->calloc(1, sizeof(cmark_map)); map->mem = mem; map->free = free; return map; } cmark-gfm-0.1.8/test/test-cmark.hs0000644000000000000000000001117113361532343015143 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} import CMarkGFM import Test.HUnit import System.Exit import Data.Text () main :: IO () main = do counts' <- runTestTT tests case (errors counts' + failures counts') of 0 -> exitWith ExitSuccess n -> exitWith (ExitFailure n) -- The C library has its own extensive tests. -- Here we just make sure it's basically working. tests :: Test tests = TestList [ "

Hi

\n" ~=? commonmarkToHtml [] [] "# Hi" , "

dog’s

\n" ~=? commonmarkToHtml [optSmart] [] "dog's" , "

trick

\n" ~=? commonmarkToHtml [] [] "[trick](javascript:alert('hi'))" , ".RS\n.PP\nquote\n.RE\n" ~=? commonmarkToMan [] [] Nothing "> quote" , (Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 1, endColumn = 13})) DOCUMENT [Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 1, endColumn = 13})) PARAGRAPH [Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 1, endColumn = 6})) (TEXT "Hello ") [],Node (Just (PosInfo {startLine = 1, startColumn = 7, endLine = 1, endColumn = 13})) EMPH [Node (Just (PosInfo {startLine = 1, startColumn = 8, endLine = 1, endColumn = 12})) (TEXT "world") []]]]) ~=? commonmarkToNode [] [] "Hello *world*" , "> Hello\n> *world*\n" ~=? nodeToCommonmark [] (Just 12) (Node Nothing DOCUMENT [Node Nothing BLOCK_QUOTE [Node Nothing PARAGRAPH [Node Nothing (TEXT "Hello ") [],Node Nothing EMPH [Node Nothing (TEXT "world") []]]]]) , "

~hi~

\n" ~=? commonmarkToHtml [] [] "~hi~" , "

hi

\n" ~=? commonmarkToHtml [] [extStrikethrough] "~hi~" , (Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 1, endColumn = 4})) DOCUMENT [Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 1, endColumn = 4})) PARAGRAPH [Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 1, endColumn = 4})) STRIKETHROUGH [Node (Just (PosInfo {startLine = 1, startColumn = 2, endLine = 1, endColumn = 3})) (TEXT "hi") []]]]) ~=? commonmarkToNode [] [extStrikethrough] "~hi~" , "

www.google.com

\n" ~=? commonmarkToHtml [] [] "www.google.com" , "

www.google.com

\n" ~=? commonmarkToHtml [] [extAutolink] "www.google.com" , "

| a |\n| --- |\n| b |

\n" ~=? commonmarkToHtml [] [] "| a |\n| --- |\n| b |\n" , "\n\n\n\n\n\n\n\n\n\n\n
a
b
\n" ~=? commonmarkToHtml [] [extTable] "| a |\n| --- |\n| b |\n" , Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 3, endColumn = 17})) DOCUMENT [Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 3, endColumn = 17})) (TABLE [LeftAligned,CenterAligned,NoAlignment,RightAligned]) [Node (Just (PosInfo {startLine = 1, startColumn = 1, endLine = 1, endColumn = 17})) TABLE_ROW [Node (Just (PosInfo {startLine = 1, startColumn = 2, endLine = 1, endColumn = 4})) TABLE_CELL [Node (Just (PosInfo {startLine = 1, startColumn = 3, endLine = 1, endColumn = 3})) (TEXT "a") []],Node (Just (PosInfo {startLine = 1, startColumn = 6, endLine = 1, endColumn = 8})) TABLE_CELL [Node (Just (PosInfo {startLine = 1, startColumn = 7, endLine = 1, endColumn = 7})) (TEXT "b") []],Node (Just (PosInfo {startLine = 1, startColumn = 10, endLine = 1, endColumn = 12})) TABLE_CELL [Node (Just (PosInfo {startLine = 1, startColumn = 11, endLine = 1, endColumn = 11})) (TEXT "c") []],Node (Just (PosInfo {startLine = 1, startColumn = 14, endLine = 1, endColumn = 16})) TABLE_CELL [Node (Just (PosInfo {startLine = 1, startColumn = 15, endLine = 1, endColumn = 15})) (TEXT "d") []]],Node (Just (PosInfo {startLine = 3, startColumn = 1, endLine = 3, endColumn = 17})) TABLE_ROW [Node (Just (PosInfo {startLine = 3, startColumn = 2, endLine = 3, endColumn = 4})) TABLE_CELL [Node (Just (PosInfo {startLine = 3, startColumn = 3, endLine = 3, endColumn = 3})) (TEXT "y") []],Node (Just (PosInfo {startLine = 3, startColumn = 6, endLine = 3, endColumn = 8})) TABLE_CELL [Node (Just (PosInfo {startLine = 3, startColumn = 7, endLine = 3, endColumn = 7})) (TEXT "o") []],Node (Just (PosInfo {startLine = 3, startColumn = 10, endLine = 3, endColumn = 12})) TABLE_CELL [Node (Just (PosInfo {startLine = 3, startColumn = 11, endLine = 3, endColumn = 11})) (TEXT "s") []],Node (Just (PosInfo {startLine = 3, startColumn = 14, endLine = 3, endColumn = 16})) TABLE_CELL [Node (Just (PosInfo {startLine = 3, startColumn = 15, endLine = 3, endColumn = 15})) (TEXT "h") []]]]] ~=? commonmarkToNode [] [extTable] "| a | b | c | d |\n| :-- | :-: | --- | --: |\n| y | o | s | h |" , "\n" ~=? commonmarkToHtml [optUnsafe] [] "<xmp>" , "&lt;xmp>\n" ~=? commonmarkToHtml [optUnsafe] [extTagfilter] "<xmp>" ] �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/bench/bench-cmark.hs����������������������������������������������������������������0000644�0000000�0000000�00000003072�13316270220�015335� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������import qualified Cheapskate as Cheapskate import qualified Cheapskate.Html as CheapskateHtml import qualified CMarkGFM as CMarkGFM import qualified Text.Sundown.Html.Text as Sundown import qualified Text.Discount as Discount import qualified Text.Blaze.Html.Renderer.Text as Blaze import qualified Text.Markdown as Markdown import Data.Text (Text) import Data.Text as T import Data.Text.Lazy (fromChunks, toChunks) import Data.Text.IO as T import Criterion.Main import Criterion.Monad import System.Environment (getArgs) main :: IO () main = do sample <- T.readFile "bench/sample.md" defaultMain [ mkBench "cheapskate" (T.concat . toChunks . Blaze.renderHtml . CheapskateHtml.renderDoc . Cheapskate.markdown Cheapskate.def) sample , mkBench "discount" (Discount.parseMarkdownUtf8 []) sample , mkBench "markdown" (T.concat . toChunks . Blaze.renderHtml . Markdown.markdown Markdown.def . fromChunks . (:[])) sample , mkBench "cmark" (CMarkGFM.commonmarkToHtml [] []) sample ] -- Note: when full-sample.md rather than sample.md is used markdown -- hangs (> 1 minute). -- even with sample.md, sundown gives this error -- , mkBench "sundown" (Sundown.renderHtml Sundown.noExtensions Sundown.noHtmlModes False Nothing) sample -- bench-cmark(50437,0x7fff7bfbe310) malloc: *** error for object 0x7ffde3d00928: incorrect checksum for freed object - object was probably modified after being freed. -- *** set a breakpoint in malloc_error_break to debug mkBench :: String -> (Text -> Text) -> Text -> Benchmark mkBench name converter inp = bench name $ nf converter inp ����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/LICENSE�����������������������������������������������������������������������������0000644�0000000�0000000�00000014370�13315273412�012565� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������Copyright (c) 2014, John MacFarlane All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of John MacFarlane nor the names of other contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. ---- libcmark Copyright (c) 2014, John MacFarlane All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. ---- houdini.h, houdini_href_e.c, houdini_html_e.c, houdini_html_u.c, html_unescape.gperf, html_unescape.h derive from https://github.com/vmg/houdini (with some modifications) Copyright (C) 2012 Vicent Martí Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----- buffer.h, buffer.c, chunk.h are derived from code (C) 2012 Github, Inc. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----- utf8.c and utf8.c are derived from utf8proc (<http://www.public-software-group.org/utf8proc>), (C) 2009 Public Software Group e. V., Berlin, Germany. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/Setup.hs����������������������������������������������������������������������������0000644�0000000�0000000�00000000056�13315273412�013210� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������import Distribution.Simple main = defaultMain ����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cmark-gfm.cabal���������������������������������������������������������������������0000644�0000000�0000000�00000012223�13442337227�014411� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������name: cmark-gfm version: 0.1.8 synopsis: Fast, accurate GitHub Flavored Markdown parser and renderer description: This package provides Haskell bindings for <https://github.com/github/cmark-gfm libcmark-gfm>, the reference parser for <https://github.github.com/gfm/ GitHub Flavored Markdown>, a fully specified variant of Markdown. It includes sources for libcmark-gfm (0.28.3.gfm.20) and does not require prior installation of the C library. homepage: https://github.com/kivikakk/cmark-gfm-hs license: BSD3 license-file: LICENSE author: Ashe Connor maintainer: kivikakk@github.com copyright: (C) 2015--17 John MacFarlane, (C) 2017--19 Ashe Connor category: Text tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.2, GHC == 7.10.3 build-type: Simple extra-source-files: README.md changelog cbits/chunk.h cbits/cmark-gfm_export.h cbits/debug.h cbits/inlines.h cbits/cmark-gfm.h cbits/houdini.h cbits/references.h cbits/utf8.h cbits/parser.h cbits/cmark-gfm_version.h cbits/html_unescape.h cbits/iterator.h cbits/node.h cbits/buffer.h cbits/render.h cbits/cmark_ctype.h cbits/config.h cbits/scanners.h cbits/case_fold_switch.inc cbits/entities.inc cbits/cmark-gfm-extension_api.h cbits/html.h cbits/plugin.h cbits/registry.h cbits/syntax_extension.h cbits/autolink.h cbits/cmark-gfm-core-extensions.h cbits/ext_scanners.h cbits/strikethrough.h cbits/table.h cbits/tagfilter.h cbits/tasklist.h cbits/cmark-gfm-extensions_export.h cbits/map.h cbits/footnotes.h bench/sample.md bench/full-sample.md cabal-version: 1.14 Source-repository head type: git location: git://github.com/kivikakk/cmark-gfm-hs.git flag pkgconfig default: False description: Use system libcmark-gfm via pkgconfig library exposed-modules: CMarkGFM build-depends: base >=4.5 && < 5.0, text >= 1.0 && < 1.3, bytestring if impl(ghc < 7.6) build-depends: ghc-prim >= 0.2 default-language: Haskell2010 ghc-options: -Wall -fno-warn-unused-do-bind if flag(pkgconfig) Extra-Libraries: cmark-gfm cmark-gfm-extensions else cc-options: -Wall -std=c99 Include-dirs: cbits Includes: cmark-gfm.h c-sources: cbits/houdini_html_u.c cbits/references.c cbits/utf8.c cbits/inlines.c cbits/blocks.c cbits/cmark.c cbits/iterator.c cbits/node.c cbits/buffer.c cbits/cmark_ctype.c cbits/houdini_html_e.c cbits/houdini_href_e.c cbits/scanners.c cbits/html.c cbits/man.c cbits/commonmark.c cbits/latex.c cbits/xml.c cbits/render.c cbits/arena.c cbits/linked_list.c cbits/plaintext.c cbits/plugin.c cbits/registry.c cbits/syntax_extension.c cbits/autolink.c cbits/core-extensions.c cbits/ext_scanners.c cbits/strikethrough.c cbits/table.c cbits/tagfilter.c cbits/tasklist.c cbits/footnotes.c cbits/map.c benchmark bench-cmark-gfm type: exitcode-stdio-1.0 hs-source-dirs: bench main-is: bench-cmark.hs build-depends: base, text, cmark-gfm, criterion, sundown >= 0.6 && < 0.7, cheapskate >= 0.1 && < 0.2, markdown >= 0.1 && < 0.2, discount >= 0.1 && < 0.2, blaze-html >= 0.7 && < 0.10 ghc-options: -O2 default-language: Haskell2010 Test-Suite test-cmark-gfm type: exitcode-stdio-1.0 main-is: test-cmark.hs hs-source-dirs: test build-depends: base, cmark-gfm, text, HUnit >= 1.2 && < 1.7 ghc-options: -Wall -fno-warn-unused-do-bind -threaded default-language: Haskell98 �����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/README.md���������������������������������������������������������������������������0000644�0000000�0000000�00000006345�13315273412�013042� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-hs ============ This package provides Haskell bindings for [libcmark-gfm], the reference parser for [GitHub Flavored Markdown], a fully specified variant of Markdown. It includes sources for [libcmark-gfm] and does not require prior installation of the C library. cmark provides the following advantages over existing Markdown libraries for Haskell: - **Speed:** cmark can render a Markdown version of *War and Peace* in the blink of an eye. Conversion speed is on par with the [sundown] library, though we were unable to benchmark precisely, because [sundown] raised a malloc error when compiled into our benchmark suite. Relative to other Haskell Markdown libraries: cmark was 82 times faster than [cheapskate], 59 times faster than [markdown], 105 times faster than [pandoc], and 3 times faster than [discount]. - **Memory footprint:** Memory footprint is on par with [sundown]. On one sample, the library uses a fourth the memory that [markdown] uses, and less than a tenth the memory that [pandoc] uses. - **Robustness:** cmark can handle whatever is thrown at it, without the exponential blowups in parsing time that sometimes afflict other libraries. (The input `bench/full-sample.md`, for example, causes both [pandoc] and [markdown] to grind to a halt.) [libcmark-gfm] has been extensively fuzz-tested. - **Accuracy:** cmark passes the CommonMark spec's suite of over 600 conformance tests. - **Standardization:** Since there is a spec and a comprehensive suite of tests, we can have a high degree of confidence that any two CommonMark implementations will behave the same. Thus, for example, one could use this library for server-side rendering and [commonmark.js] for client-side previewing. - **Multiple renderers.** Output in HTML, groff man, LaTeX, CommonMark, and a custom XML format is supported. And it is easy to write new renderers to support other formats. - **Ease of installation:** cmark is portable and has minimal dependencies. cmark does not provide Haskell versions of the whole [libcmark-gfm] API, which is built around mutable `cmark_node` objects. Instead, it provides functions for converting CommonMark to HTML (and other formats), and a function for converting CommonMark to a `Node` tree that can be processed further using Haskell. **A note on security:** This library does not attempt to sanitize HTML output. We recommend using [xss-sanitize] to filter the output, or enabling `optSafe` to filter out all raw HTML and potentially dangerous URLs. **A note on stability:** There is a good chance the API will change significantly after this early release. [GitHub Flavored Markdown]: https://github.github.com/gfm/ [libcmark-gfm]: http://github.com/github/cmark [benchmarks]: https://github.com/jgm/cmark/blob/master/benchmarks.md [cheapskate]: https://hackage.haskell.org/package/cheapskate [pandoc]: https://hackage.haskell.org/package/pandoc [sundown]: https://hackage.haskell.org/package/sundown [markdown]: https://hackage.haskell.org/package/markdown [commonmark.js]: http://github.com/jgm/commonmark.js [xss-sanitize]: https://hackage.haskell.org/package/xss-sanitize [discount]: https://hackage.haskell.org/package/discount �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/changelog���������������������������������������������������������������������������0000644�0000000�0000000�00000010551�13442337174�013436� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm 0.1.8 (14 Mar 2019) * Pull in upstream changes. cmark 0.5.6.3 (13 Mar 2019) * Use snoc instead of <> to add the null terminator. cmark 0.5.6.2 (13 Mar 2019) * Ensure that withtext adds a null terminator (#14). This fixes a regression due to PR #13, which caused random content to appear in rendered TEXT nodes. cmark-gfm 0.1.7 (13 Mar 2019) * Update to cmark-gfm 0.28.3.gfm.20. cmark 0.5.6.1 (11 Mar 2019) * Fix CString memory leaks (Anders Kaseorg). The renderer functions return a malloc’d string which the caller is expected to free. * Fix use-after-free bugs (Anders Kaseorg). `useAsCString` frees the CString after the IO action finishes executing, so passing `return` as that action can never be correct. To make sure the CString gets freed at the right time, we need a “with”-style abstraction, not just a conversion function. While we’re here replace this with `withCStringLen`, which also makes fewer copies. * Show node type on error for unknown node type. cmark-gfm 0.1.6 (17 Oct 2018) * Update to cmark-gfm 0.28.3.gfm.18. * `optUnsafe` is now exposed, instead of `optSafe`. cmark-gfm 0.1.5 (21 Aug 2018) * Update to cmark-gfm 0.28.3.gfm.15. * Fix build with system cmark-gfm (Felix Yan, #9). cmark-gfm 0.1.4 (2 Jul 2018) * Extensions work correctly on big-endian systems (Ilias Tsitsimpis). cmark-gfm 0.1.3 (10 Aug 2017) * Update to cmark-gfm 0.28.0.gfm.6. cmark-gfm 0.1.2 (09 Aug 2017) * Update to cmark-gfm 0.28.0.gfm.5. cmark-gfm 0.1.1 (03 Aug 2017) * Automatically register plugins. * Rename alignment values to not clash with `None`, `Left`. * Fix a potential use-after-free. cmark-gfm 0.1.0 (03 Aug 2017) * Update to cmark-gfm (between revisions). * Add extension support. cmark 0.5.6 (02 Aug 2017) * Update to cmark 0.28.0. cmark 0.5.5.1 (20 Mar 2017) * Update version bound for HUnit. cmark 0.5.5 (31 Jan 2017) * Update to cmark 0.27.1. * Update version bounds for dependencies. cmark 0.5.4 (18 Nov 2016) * Update to cmark 0.27.0. cmark 0.5.3.1 (16 Jul 2016) * Remove unnecessary typedef that caused problems with the build (patch from upstream). cmark 0.5.3 (15 Jul 2016) * Update to cmark 0.26.0. * Added appveyor CI. cmark 0.5.2.1 (22 May 2016) * New .travis.yml - test with stack, cabal on many versions. * Increase upper bound of base (Utku Demir). cmark 0.5.2 (26 Mar 2016) * Add flag to allow building with an installed libcmark (Jens Petersen). * Updated to libcmark 0.25.2. cmark 0.5.1 (21 Jan 2016) * Updated to libcmark 0.24.1. cmark 0.5 (29 Dec 2015) * Updated to libcmark 0.23.0. * API changes: + Added `OnEnter` and `OnExit` types. + In `NodeType`, `HRULE` is now `THEMATIC_BREAK`, `HTML` is `HTML_BLOCK`, `INLINE_HTML` is `HTML_INLINE`, `HEADER` is `HEADING`. New constructors: `CUSTOM_INLINE`, `CUSTOM_BLOCK`. cmark 0.4.1 (23 Aug 2015) * Updated to libcmark 0.22.0. * Bumped version bounds for HUnit. cmark 0.4.0.1 (14 Jul 2015) * API changes: + Added `commonmarkToLaTeX`, `nodeToLaTeX`, `optSafe`. + Changed type of `commonmarkToMan` and `nodeToMan`, adding `Maybe Int` param for width. + Changed type of `nodeToCommonMark`, changing the `Int` width parameter to a `Maybe Int`. * Updated to cmark 0.21 sources. cmark 0.3.4 (08 Jun 2015) * Updated to libcmark 0.20.0. cmark 0.3.3.1 (28 May 2015) * Changed name Bench.hs -> bench-cmark.hs. * Benchmark: don't benchmark pandoc (circular dependency). cmark 0.3.3 (26 May 2015) * Added `nodeToHtml`, `nodeToMan`, `nodeToXml`. * Added version bounds for text (Albert Krewinkel). cmark 0.3.2 (28 Apr 2015) * Updated libcmark C sources to 0.19.0. * Fixes to avoid warning for earlier ghc versions. * Refactored, removing the `io` convenience function. * Removed unnecessary `unsafePerformIO` on `fromtext`. * `fromtext`: use `ByteString.useAsCString` + explicit `encodeUtf8`. cmark 0.3.1 (29 Mar 2015) * Added nodeToCommonmark. * Removed mtl from build-depends. * Updated source info in README, cabal. * Updated C sources. * Put all the C functions in the IO monad, and ensure that memory allocated by the C library is freed at the right time. * Added a rudimentary test suite. * Properly free c-allocated resources. * Removed bindings to nonexistent setters for source pos attributes. �������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/chunk.h�����������������������������������������������������������������������0000644�0000000�0000000�00000006465�13442034251�014150� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_CHUNK_H #define CMARK_CHUNK_H #include <string.h> #include <stdlib.h> #include <assert.h> #include "cmark-gfm.h" #include "buffer.h" #include "memory.h" #include "cmark_ctype.h" #define CMARK_CHUNK_EMPTY \ { NULL, 0, 0 } typedef struct cmark_chunk { unsigned char *data; bufsize_t len; bufsize_t alloc; // also implies a NULL-terminated string } cmark_chunk; static CMARK_INLINE void cmark_chunk_free(cmark_mem *mem, cmark_chunk *c) { if (c->alloc) mem->free(c->data); c->data = NULL; c->alloc = 0; c->len = 0; } static CMARK_INLINE void cmark_chunk_ltrim(cmark_chunk *c) { assert(!c->alloc); while (c->len && cmark_isspace(c->data[0])) { c->data++; c->len--; } } static CMARK_INLINE void cmark_chunk_rtrim(cmark_chunk *c) { assert(!c->alloc); while (c->len > 0) { if (!cmark_isspace(c->data[c->len - 1])) break; c->len--; } } static CMARK_INLINE void cmark_chunk_trim(cmark_chunk *c) { cmark_chunk_ltrim(c); cmark_chunk_rtrim(c); } static CMARK_INLINE bufsize_t cmark_chunk_strchr(cmark_chunk *ch, int c, bufsize_t offset) { const unsigned char *p = (unsigned char *)memchr(ch->data + offset, c, ch->len - offset); return p ? (bufsize_t)(p - ch->data) : ch->len; } static CMARK_INLINE const char *cmark_chunk_to_cstr(cmark_mem *mem, cmark_chunk *c) { unsigned char *str; if (c->alloc) { return (char *)c->data; } str = (unsigned char *)mem->calloc(c->len + 1, 1); if (c->len > 0) { memcpy(str, c->data, c->len); } str[c->len] = 0; c->data = str; c->alloc = 1; return (char *)str; } static CMARK_INLINE void cmark_chunk_set_cstr(cmark_mem *mem, cmark_chunk *c, const char *str) { unsigned char *old = c->alloc ? c->data : NULL; if (str == NULL) { c->len = 0; c->data = NULL; c->alloc = 0; } else { c->len = (bufsize_t)strlen(str); c->data = (unsigned char *)mem->calloc(c->len + 1, 1); c->alloc = 1; memcpy(c->data, str, c->len + 1); } if (old != NULL) { mem->free(old); } } static CMARK_INLINE cmark_chunk cmark_chunk_literal(const char *data) { bufsize_t len = data ? (bufsize_t)strlen(data) : 0; cmark_chunk c = {(unsigned char *)data, len, 0}; return c; } static CMARK_INLINE cmark_chunk cmark_chunk_dup(const cmark_chunk *ch, bufsize_t pos, bufsize_t len) { cmark_chunk c = {ch->data + pos, len, 0}; return c; } static CMARK_INLINE cmark_chunk cmark_chunk_buf_detach(cmark_strbuf *buf) { cmark_chunk c; c.len = buf->size; c.data = cmark_strbuf_detach(buf); c.alloc = 1; return c; } /* trim_new variants are to be used when the source chunk may or may not be * allocated; forces a newly allocated chunk. */ static CMARK_INLINE cmark_chunk cmark_chunk_ltrim_new(cmark_mem *mem, cmark_chunk *c) { cmark_chunk r = cmark_chunk_dup(c, 0, c->len); cmark_chunk_ltrim(&r); cmark_chunk_to_cstr(mem, &r); return r; } static CMARK_INLINE cmark_chunk cmark_chunk_rtrim_new(cmark_mem *mem, cmark_chunk *c) { cmark_chunk r = cmark_chunk_dup(c, 0, c->len); cmark_chunk_rtrim(&r); cmark_chunk_to_cstr(mem, &r); return r; } #endif �����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/cmark-gfm_export.h������������������������������������������������������������0000644�0000000�0000000�00000002072�13442034251�016273� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������ #ifndef CMARK_GFM_EXPORT_H #define CMARK_GFM_EXPORT_H #ifdef CMARK_GFM_STATIC_DEFINE # define CMARK_GFM_EXPORT # define CMARK_GFM_NO_EXPORT #else # ifndef CMARK_GFM_EXPORT # ifdef libcmark_gfm_EXPORTS /* We are building this library */ # define CMARK_GFM_EXPORT __attribute__((visibility("default"))) # else /* We are using this library */ # define CMARK_GFM_EXPORT __attribute__((visibility("default"))) # endif # endif # ifndef CMARK_GFM_NO_EXPORT # define CMARK_GFM_NO_EXPORT __attribute__((visibility("hidden"))) # endif #endif #ifndef CMARK_GFM_DEPRECATED # define CMARK_GFM_DEPRECATED __attribute__ ((__deprecated__)) #endif #ifndef CMARK_GFM_DEPRECATED_EXPORT # define CMARK_GFM_DEPRECATED_EXPORT CMARK_GFM_EXPORT CMARK_GFM_DEPRECATED #endif #ifndef CMARK_GFM_DEPRECATED_NO_EXPORT # define CMARK_GFM_DEPRECATED_NO_EXPORT CMARK_GFM_NO_EXPORT CMARK_GFM_DEPRECATED #endif #if 0 /* DEFINE_NO_DEPRECATED */ # ifndef CMARK_GFM_NO_DEPRECATED # define CMARK_GFM_NO_DEPRECATED # endif #endif #endif /* CMARK_GFM_EXPORT_H */ ����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/debug.h�����������������������������������������������������������������������0000644�0000000�0000000�00000001752�13315273412�014123� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_DEBUG_H #define CMARK_DEBUG_H #include <stdio.h> #include <errno.h> #include <string.h> #ifdef NDEBUG #define debug(M, ...) #else #define debug(M, ...) \ fprintf(stderr, "DEBUG %s:%d: " M "\n", __FILE__, __LINE__, ##__VA_ARGS__) #endif #define clean_errno() (errno == 0 ? "None" : strerror(errno)) #define log_err(M, ...) \ fprintf(stderr, "[ERROR] (%s:%d: errno: %s) " M "\n", __FILE__, __LINE__, \ clean_errno(), ##__VA_ARGS__) #define log_warn(M, ...) \ fprintf(stderr, "[WARN] (%s:%d: errno: %s) " M "\n", __FILE__, __LINE__, \ clean_errno(), ##__VA_ARGS__) #define log_info(M, ...) fprintf(stderr, "[INFO] (%s:%d) " M "\n", __FILE__, \ __LINE__, ##__VA_ARGS__) #define check(A, M, ...) \ if(!(A)) { log_err(M, ##__VA_ARGS__); errno=0; goto error; } #define sentinel(M, ...) \ { log_err(M, ##__VA_ARGS__); errno=0; goto error; } #define check_debug(A, M, ...) \ if(!(A)) { debug(M, ##__VA_ARGS__); errno=0; goto error; } #endif ����������������������cmark-gfm-0.1.8/cbits/inlines.h���������������������������������������������������������������������0000644�0000000�0000000�00000001371�13442034251�014470� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_INLINES_H #define CMARK_INLINES_H #ifdef __cplusplus extern "C" { #endif #include "references.h" cmark_chunk cmark_clean_url(cmark_mem *mem, cmark_chunk *url); cmark_chunk cmark_clean_title(cmark_mem *mem, cmark_chunk *title); CMARK_GFM_EXPORT void cmark_parse_inlines(cmark_parser *parser, cmark_node *parent, cmark_map *refmap, int options); bufsize_t cmark_parse_reference_inline(cmark_mem *mem, cmark_chunk *input, cmark_map *refmap); void cmark_inlines_add_special_character(unsigned char c, bool emphasis); void cmark_inlines_remove_special_character(unsigned char c, bool emphasis); #ifdef __cplusplus } #endif #endif �����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/cmark-gfm.h�������������������������������������������������������������������0000644�0000000�0000000�00000062301�13442034251�014673� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_H #define CMARK_GFM_H #include <stdio.h> #include <stdint.h> #include "cmark-gfm_export.h" #include "cmark-gfm_version.h" #ifdef __cplusplus extern "C" { #endif /** # NAME * * **cmark-gfm** - CommonMark parsing, manipulating, and rendering */ /** # DESCRIPTION * * ## Simple Interface */ /** Convert 'text' (assumed to be a UTF-8 encoded string with length * 'len') from CommonMark Markdown to HTML, returning a null-terminated, * UTF-8-encoded string. It is the caller's responsibility * to free the returned buffer. */ CMARK_GFM_EXPORT char *cmark_markdown_to_html(const char *text, size_t len, int options); /** ## Node Structure */ #define CMARK_NODE_TYPE_PRESENT (0x8000) #define CMARK_NODE_TYPE_BLOCK (CMARK_NODE_TYPE_PRESENT | 0x0000) #define CMARK_NODE_TYPE_INLINE (CMARK_NODE_TYPE_PRESENT | 0x4000) #define CMARK_NODE_TYPE_MASK (0xc000) #define CMARK_NODE_VALUE_MASK (0x3fff) typedef enum { /* Error status */ CMARK_NODE_NONE = 0x0000, /* Block */ CMARK_NODE_DOCUMENT = CMARK_NODE_TYPE_BLOCK | 0x0001, CMARK_NODE_BLOCK_QUOTE = CMARK_NODE_TYPE_BLOCK | 0x0002, CMARK_NODE_LIST = CMARK_NODE_TYPE_BLOCK | 0x0003, CMARK_NODE_ITEM = CMARK_NODE_TYPE_BLOCK | 0x0004, CMARK_NODE_CODE_BLOCK = CMARK_NODE_TYPE_BLOCK | 0x0005, CMARK_NODE_HTML_BLOCK = CMARK_NODE_TYPE_BLOCK | 0x0006, CMARK_NODE_CUSTOM_BLOCK = CMARK_NODE_TYPE_BLOCK | 0x0007, CMARK_NODE_PARAGRAPH = CMARK_NODE_TYPE_BLOCK | 0x0008, CMARK_NODE_HEADING = CMARK_NODE_TYPE_BLOCK | 0x0009, CMARK_NODE_THEMATIC_BREAK = CMARK_NODE_TYPE_BLOCK | 0x000a, CMARK_NODE_FOOTNOTE_DEFINITION = CMARK_NODE_TYPE_BLOCK | 0x000b, /* Inline */ CMARK_NODE_TEXT = CMARK_NODE_TYPE_INLINE | 0x0001, CMARK_NODE_SOFTBREAK = CMARK_NODE_TYPE_INLINE | 0x0002, CMARK_NODE_LINEBREAK = CMARK_NODE_TYPE_INLINE | 0x0003, CMARK_NODE_CODE = CMARK_NODE_TYPE_INLINE | 0x0004, CMARK_NODE_HTML_INLINE = CMARK_NODE_TYPE_INLINE | 0x0005, CMARK_NODE_CUSTOM_INLINE = CMARK_NODE_TYPE_INLINE | 0x0006, CMARK_NODE_EMPH = CMARK_NODE_TYPE_INLINE | 0x0007, CMARK_NODE_STRONG = CMARK_NODE_TYPE_INLINE | 0x0008, CMARK_NODE_LINK = CMARK_NODE_TYPE_INLINE | 0x0009, CMARK_NODE_IMAGE = CMARK_NODE_TYPE_INLINE | 0x000a, CMARK_NODE_FOOTNOTE_REFERENCE = CMARK_NODE_TYPE_INLINE | 0x000b, } cmark_node_type; extern cmark_node_type CMARK_NODE_LAST_BLOCK; extern cmark_node_type CMARK_NODE_LAST_INLINE; /* For backwards compatibility: */ #define CMARK_NODE_HEADER CMARK_NODE_HEADING #define CMARK_NODE_HRULE CMARK_NODE_THEMATIC_BREAK #define CMARK_NODE_HTML CMARK_NODE_HTML_BLOCK #define CMARK_NODE_INLINE_HTML CMARK_NODE_HTML_INLINE typedef enum { CMARK_NO_LIST, CMARK_BULLET_LIST, CMARK_ORDERED_LIST } cmark_list_type; typedef enum { CMARK_NO_DELIM, CMARK_PERIOD_DELIM, CMARK_PAREN_DELIM } cmark_delim_type; typedef struct cmark_node cmark_node; typedef struct cmark_parser cmark_parser; typedef struct cmark_iter cmark_iter; typedef struct cmark_syntax_extension cmark_syntax_extension; /** * ## Custom memory allocator support */ /** Defines the memory allocation functions to be used by CMark * when parsing and allocating a document tree */ typedef struct cmark_mem { void *(*calloc)(size_t, size_t); void *(*realloc)(void *, size_t); void (*free)(void *); } cmark_mem; /** The default memory allocator; uses the system's calloc, * realloc and free. */ CMARK_GFM_EXPORT cmark_mem *cmark_get_default_mem_allocator(); /** An arena allocator; uses system calloc to allocate large * slabs of memory. Memory in these slabs is not reused at all. */ CMARK_GFM_EXPORT cmark_mem *cmark_get_arena_mem_allocator(); /** Resets the arena allocator, quickly returning all used memory * to the operating system. */ CMARK_GFM_EXPORT void cmark_arena_reset(void); /** Callback for freeing user data with a 'cmark_mem' context. */ typedef void (*cmark_free_func) (cmark_mem *mem, void *user_data); /* * ## Basic data structures * * To keep dependencies to the strict minimum, libcmark implements * its own versions of "classic" data structures. */ /** * ### Linked list */ /** A generic singly linked list. */ typedef struct _cmark_llist { struct _cmark_llist *next; void *data; } cmark_llist; /** Append an element to the linked list, return the possibly modified * head of the list. */ CMARK_GFM_EXPORT cmark_llist * cmark_llist_append (cmark_mem * mem, cmark_llist * head, void * data); /** Free the list starting with 'head', calling 'free_func' with the * data pointer of each of its elements */ CMARK_GFM_EXPORT void cmark_llist_free_full (cmark_mem * mem, cmark_llist * head, cmark_free_func free_func); /** Free the list starting with 'head' */ CMARK_GFM_EXPORT void cmark_llist_free (cmark_mem * mem, cmark_llist * head); /** * ## Creating and Destroying Nodes */ /** Creates a new node of type 'type'. Note that the node may have * other required properties, which it is the caller's responsibility * to assign. */ CMARK_GFM_EXPORT cmark_node *cmark_node_new(cmark_node_type type); /** Same as `cmark_node_new`, but explicitly listing the memory * allocator used to allocate the node. Note: be sure to use the same * allocator for every node in a tree, or bad things can happen. */ CMARK_GFM_EXPORT cmark_node *cmark_node_new_with_mem(cmark_node_type type, cmark_mem *mem); CMARK_GFM_EXPORT cmark_node *cmark_node_new_with_ext(cmark_node_type type, cmark_syntax_extension *extension); CMARK_GFM_EXPORT cmark_node *cmark_node_new_with_mem_and_ext(cmark_node_type type, cmark_mem *mem, cmark_syntax_extension *extension); /** Frees the memory allocated for a node and any children. */ CMARK_GFM_EXPORT void cmark_node_free(cmark_node *node); /** * ## Tree Traversal */ /** Returns the next node in the sequence after 'node', or NULL if * there is none. */ CMARK_GFM_EXPORT cmark_node *cmark_node_next(cmark_node *node); /** Returns the previous node in the sequence after 'node', or NULL if * there is none. */ CMARK_GFM_EXPORT cmark_node *cmark_node_previous(cmark_node *node); /** Returns the parent of 'node', or NULL if there is none. */ CMARK_GFM_EXPORT cmark_node *cmark_node_parent(cmark_node *node); /** Returns the first child of 'node', or NULL if 'node' has no children. */ CMARK_GFM_EXPORT cmark_node *cmark_node_first_child(cmark_node *node); /** Returns the last child of 'node', or NULL if 'node' has no children. */ CMARK_GFM_EXPORT cmark_node *cmark_node_last_child(cmark_node *node); /** * ## Iterator * * An iterator will walk through a tree of nodes, starting from a root * node, returning one node at a time, together with information about * whether the node is being entered or exited. The iterator will * first descend to a child node, if there is one. When there is no * child, the iterator will go to the next sibling. When there is no * next sibling, the iterator will return to the parent (but with * a 'cmark_event_type' of `CMARK_EVENT_EXIT`). The iterator will * return `CMARK_EVENT_DONE` when it reaches the root node again. * One natural application is an HTML renderer, where an `ENTER` event * outputs an open tag and an `EXIT` event outputs a close tag. * An iterator might also be used to transform an AST in some systematic * way, for example, turning all level-3 headings into regular paragraphs. * * void * usage_example(cmark_node *root) { * cmark_event_type ev_type; * cmark_iter *iter = cmark_iter_new(root); * * while ((ev_type = cmark_iter_next(iter)) != CMARK_EVENT_DONE) { * cmark_node *cur = cmark_iter_get_node(iter); * // Do something with `cur` and `ev_type` * } * * cmark_iter_free(iter); * } * * Iterators will never return `EXIT` events for leaf nodes, which are nodes * of type: * * * CMARK_NODE_HTML_BLOCK * * CMARK_NODE_THEMATIC_BREAK * * CMARK_NODE_CODE_BLOCK * * CMARK_NODE_TEXT * * CMARK_NODE_SOFTBREAK * * CMARK_NODE_LINEBREAK * * CMARK_NODE_CODE * * CMARK_NODE_HTML_INLINE * * Nodes must only be modified after an `EXIT` event, or an `ENTER` event for * leaf nodes. */ typedef enum { CMARK_EVENT_NONE, CMARK_EVENT_DONE, CMARK_EVENT_ENTER, CMARK_EVENT_EXIT } cmark_event_type; /** Creates a new iterator starting at 'root'. The current node and event * type are undefined until 'cmark_iter_next' is called for the first time. * The memory allocated for the iterator should be released using * 'cmark_iter_free' when it is no longer needed. */ CMARK_GFM_EXPORT cmark_iter *cmark_iter_new(cmark_node *root); /** Frees the memory allocated for an iterator. */ CMARK_GFM_EXPORT void cmark_iter_free(cmark_iter *iter); /** Advances to the next node and returns the event type (`CMARK_EVENT_ENTER`, * `CMARK_EVENT_EXIT` or `CMARK_EVENT_DONE`). */ CMARK_GFM_EXPORT cmark_event_type cmark_iter_next(cmark_iter *iter); /** Returns the current node. */ CMARK_GFM_EXPORT cmark_node *cmark_iter_get_node(cmark_iter *iter); /** Returns the current event type. */ CMARK_GFM_EXPORT cmark_event_type cmark_iter_get_event_type(cmark_iter *iter); /** Returns the root node. */ CMARK_GFM_EXPORT cmark_node *cmark_iter_get_root(cmark_iter *iter); /** Resets the iterator so that the current node is 'current' and * the event type is 'event_type'. The new current node must be a * descendant of the root node or the root node itself. */ CMARK_GFM_EXPORT void cmark_iter_reset(cmark_iter *iter, cmark_node *current, cmark_event_type event_type); /** * ## Accessors */ /** Returns the user data of 'node'. */ CMARK_GFM_EXPORT void *cmark_node_get_user_data(cmark_node *node); /** Sets arbitrary user data for 'node'. Returns 1 on success, * 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_user_data(cmark_node *node, void *user_data); /** Set free function for user data */ CMARK_GFM_EXPORT int cmark_node_set_user_data_free_func(cmark_node *node, cmark_free_func free_func); /** Returns the type of 'node', or `CMARK_NODE_NONE` on error. */ CMARK_GFM_EXPORT cmark_node_type cmark_node_get_type(cmark_node *node); /** Like 'cmark_node_get_type', but returns a string representation of the type, or `"<unknown>"`. */ CMARK_GFM_EXPORT const char *cmark_node_get_type_string(cmark_node *node); /** Returns the string contents of 'node', or an empty string if none is set. Returns NULL if called on a node that does not have string content. */ CMARK_GFM_EXPORT const char *cmark_node_get_literal(cmark_node *node); /** Sets the string contents of 'node'. Returns 1 on success, * 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_literal(cmark_node *node, const char *content); /** Returns the heading level of 'node', or 0 if 'node' is not a heading. */ CMARK_GFM_EXPORT int cmark_node_get_heading_level(cmark_node *node); /* For backwards compatibility */ #define cmark_node_get_header_level cmark_node_get_heading_level #define cmark_node_set_header_level cmark_node_set_heading_level /** Sets the heading level of 'node', returning 1 on success and 0 on error. */ CMARK_GFM_EXPORT int cmark_node_set_heading_level(cmark_node *node, int level); /** Returns the list type of 'node', or `CMARK_NO_LIST` if 'node' * is not a list. */ CMARK_GFM_EXPORT cmark_list_type cmark_node_get_list_type(cmark_node *node); /** Sets the list type of 'node', returning 1 on success and 0 on error. */ CMARK_GFM_EXPORT int cmark_node_set_list_type(cmark_node *node, cmark_list_type type); /** Returns the list delimiter type of 'node', or `CMARK_NO_DELIM` if 'node' * is not a list. */ CMARK_GFM_EXPORT cmark_delim_type cmark_node_get_list_delim(cmark_node *node); /** Sets the list delimiter type of 'node', returning 1 on success and 0 * on error. */ CMARK_GFM_EXPORT int cmark_node_set_list_delim(cmark_node *node, cmark_delim_type delim); /** Returns starting number of 'node', if it is an ordered list, otherwise 0. */ CMARK_GFM_EXPORT int cmark_node_get_list_start(cmark_node *node); /** Sets starting number of 'node', if it is an ordered list. Returns 1 * on success, 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_list_start(cmark_node *node, int start); /** Returns 1 if 'node' is a tight list, 0 otherwise. */ CMARK_GFM_EXPORT int cmark_node_get_list_tight(cmark_node *node); /** Sets the "tightness" of a list. Returns 1 on success, 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_list_tight(cmark_node *node, int tight); /** Returns the info string from a fenced code block. */ CMARK_GFM_EXPORT const char *cmark_node_get_fence_info(cmark_node *node); /** Sets the info string in a fenced code block, returning 1 on * success and 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_fence_info(cmark_node *node, const char *info); /** Sets code blocks fencing details */ CMARK_GFM_EXPORT int cmark_node_set_fenced(cmark_node * node, int fenced, int length, int offset, char character); /** Returns code blocks fencing details */ CMARK_GFM_EXPORT int cmark_node_get_fenced(cmark_node *node, int *length, int *offset, char *character); /** Returns the URL of a link or image 'node', or an empty string if no URL is set. Returns NULL if called on a node that is not a link or image. */ CMARK_GFM_EXPORT const char *cmark_node_get_url(cmark_node *node); /** Sets the URL of a link or image 'node'. Returns 1 on success, * 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_url(cmark_node *node, const char *url); /** Returns the title of a link or image 'node', or an empty string if no title is set. Returns NULL if called on a node that is not a link or image. */ CMARK_GFM_EXPORT const char *cmark_node_get_title(cmark_node *node); /** Sets the title of a link or image 'node'. Returns 1 on success, * 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_title(cmark_node *node, const char *title); /** Returns the literal "on enter" text for a custom 'node', or an empty string if no on_enter is set. Returns NULL if called on a non-custom node. */ CMARK_GFM_EXPORT const char *cmark_node_get_on_enter(cmark_node *node); /** Sets the literal text to render "on enter" for a custom 'node'. Any children of the node will be rendered after this text. Returns 1 on success 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_on_enter(cmark_node *node, const char *on_enter); /** Returns the literal "on exit" text for a custom 'node', or an empty string if no on_exit is set. Returns NULL if called on a non-custom node. */ CMARK_GFM_EXPORT const char *cmark_node_get_on_exit(cmark_node *node); /** Sets the literal text to render "on exit" for a custom 'node'. Any children of the node will be rendered before this text. Returns 1 on success 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_set_on_exit(cmark_node *node, const char *on_exit); /** Returns the line on which 'node' begins. */ CMARK_GFM_EXPORT int cmark_node_get_start_line(cmark_node *node); /** Returns the column at which 'node' begins. */ CMARK_GFM_EXPORT int cmark_node_get_start_column(cmark_node *node); /** Returns the line on which 'node' ends. */ CMARK_GFM_EXPORT int cmark_node_get_end_line(cmark_node *node); /** Returns the column at which 'node' ends. */ CMARK_GFM_EXPORT int cmark_node_get_end_column(cmark_node *node); /** * ## Tree Manipulation */ /** Unlinks a 'node', removing it from the tree, but not freeing its * memory. (Use 'cmark_node_free' for that.) */ CMARK_GFM_EXPORT void cmark_node_unlink(cmark_node *node); /** Inserts 'sibling' before 'node'. Returns 1 on success, 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_insert_before(cmark_node *node, cmark_node *sibling); /** Inserts 'sibling' after 'node'. Returns 1 on success, 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_insert_after(cmark_node *node, cmark_node *sibling); /** Replaces 'oldnode' with 'newnode' and unlinks 'oldnode' (but does * not free its memory). * Returns 1 on success, 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_replace(cmark_node *oldnode, cmark_node *newnode); /** Adds 'child' to the beginning of the children of 'node'. * Returns 1 on success, 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_prepend_child(cmark_node *node, cmark_node *child); /** Adds 'child' to the end of the children of 'node'. * Returns 1 on success, 0 on failure. */ CMARK_GFM_EXPORT int cmark_node_append_child(cmark_node *node, cmark_node *child); /** Consolidates adjacent text nodes. */ CMARK_GFM_EXPORT void cmark_consolidate_text_nodes(cmark_node *root); /** Ensures a node and all its children own their own chunk memory. */ CMARK_GFM_EXPORT void cmark_node_own(cmark_node *root); /** * ## Parsing * * Simple interface: * * cmark_node *document = cmark_parse_document("Hello *world*", 13, * CMARK_OPT_DEFAULT); * * Streaming interface: * * cmark_parser *parser = cmark_parser_new(CMARK_OPT_DEFAULT); * FILE *fp = fopen("myfile.md", "rb"); * while ((bytes = fread(buffer, 1, sizeof(buffer), fp)) > 0) { * cmark_parser_feed(parser, buffer, bytes); * if (bytes < sizeof(buffer)) { * break; * } * } * document = cmark_parser_finish(parser); * cmark_parser_free(parser); */ /** Creates a new parser object. */ CMARK_GFM_EXPORT cmark_parser *cmark_parser_new(int options); /** Creates a new parser object with the given memory allocator */ CMARK_GFM_EXPORT cmark_parser *cmark_parser_new_with_mem(int options, cmark_mem *mem); /** Frees memory allocated for a parser object. */ CMARK_GFM_EXPORT void cmark_parser_free(cmark_parser *parser); /** Feeds a string of length 'len' to 'parser'. */ CMARK_GFM_EXPORT void cmark_parser_feed(cmark_parser *parser, const char *buffer, size_t len); /** Finish parsing and return a pointer to a tree of nodes. */ CMARK_GFM_EXPORT cmark_node *cmark_parser_finish(cmark_parser *parser); /** Parse a CommonMark document in 'buffer' of length 'len'. * Returns a pointer to a tree of nodes. The memory allocated for * the node tree should be released using 'cmark_node_free' * when it is no longer needed. */ CMARK_GFM_EXPORT cmark_node *cmark_parse_document(const char *buffer, size_t len, int options); /** Parse a CommonMark document in file 'f', returning a pointer to * a tree of nodes. The memory allocated for the node tree should be * released using 'cmark_node_free' when it is no longer needed. */ CMARK_GFM_EXPORT cmark_node *cmark_parse_file(FILE *f, int options); /** * ## Rendering */ /** Render a 'node' tree as XML. It is the caller's responsibility * to free the returned buffer. */ CMARK_GFM_EXPORT char *cmark_render_xml(cmark_node *root, int options); /** As for 'cmark_render_xml', but specifying the allocator to use for * the resulting string. */ CMARK_GFM_EXPORT char *cmark_render_xml_with_mem(cmark_node *root, int options, cmark_mem *mem); /** Render a 'node' tree as an HTML fragment. It is up to the user * to add an appropriate header and footer. It is the caller's * responsibility to free the returned buffer. */ CMARK_GFM_EXPORT char *cmark_render_html(cmark_node *root, int options, cmark_llist *extensions); /** As for 'cmark_render_html', but specifying the allocator to use for * the resulting string. */ CMARK_GFM_EXPORT char *cmark_render_html_with_mem(cmark_node *root, int options, cmark_llist *extensions, cmark_mem *mem); /** Render a 'node' tree as a groff man page, without the header. * It is the caller's responsibility to free the returned buffer. */ CMARK_GFM_EXPORT char *cmark_render_man(cmark_node *root, int options, int width); /** As for 'cmark_render_man', but specifying the allocator to use for * the resulting string. */ CMARK_GFM_EXPORT char *cmark_render_man_with_mem(cmark_node *root, int options, int width, cmark_mem *mem); /** Render a 'node' tree as a commonmark document. * It is the caller's responsibility to free the returned buffer. */ CMARK_GFM_EXPORT char *cmark_render_commonmark(cmark_node *root, int options, int width); /** As for 'cmark_render_commonmark', but specifying the allocator to use for * the resulting string. */ CMARK_GFM_EXPORT char *cmark_render_commonmark_with_mem(cmark_node *root, int options, int width, cmark_mem *mem); /** Render a 'node' tree as a plain text document. * It is the caller's responsibility to free the returned buffer. */ CMARK_GFM_EXPORT char *cmark_render_plaintext(cmark_node *root, int options, int width); /** As for 'cmark_render_plaintext', but specifying the allocator to use for * the resulting string. */ CMARK_GFM_EXPORT char *cmark_render_plaintext_with_mem(cmark_node *root, int options, int width, cmark_mem *mem); /** Render a 'node' tree as a LaTeX document. * It is the caller's responsibility to free the returned buffer. */ CMARK_GFM_EXPORT char *cmark_render_latex(cmark_node *root, int options, int width); /** As for 'cmark_render_latex', but specifying the allocator to use for * the resulting string. */ CMARK_GFM_EXPORT char *cmark_render_latex_with_mem(cmark_node *root, int options, int width, cmark_mem *mem); /** * ## Options */ /** Default options. */ #define CMARK_OPT_DEFAULT 0 /** * ### Options affecting rendering */ /** Include a `data-sourcepos` attribute on all block elements. */ #define CMARK_OPT_SOURCEPOS (1 << 1) /** Render `softbreak` elements as hard line breaks. */ #define CMARK_OPT_HARDBREAKS (1 << 2) /** Render `softbreak` elements as spaces. */ #define CMARK_OPT_NOBREAKS (1 << 4) /** * ### Options affecting parsing */ /** Legacy option (no effect). */ #define CMARK_OPT_NORMALIZE (1 << 8) /** Validate UTF-8 in the input before parsing, replacing illegal * sequences with the replacement character U+FFFD. */ #define CMARK_OPT_VALIDATE_UTF8 (1 << 9) /** Convert straight quotes to curly, --- to em dashes, -- to en dashes. */ #define CMARK_OPT_SMART (1 << 10) /** Use GitHub-style <pre lang="x"> tags for code blocks instead of <pre><code * class="language-x">. */ #define CMARK_OPT_GITHUB_PRE_LANG (1 << 11) /** Be liberal in interpreting inline HTML tags. */ #define CMARK_OPT_LIBERAL_HTML_TAG (1 << 12) /** Parse footnotes. */ #define CMARK_OPT_FOOTNOTES (1 << 13) /** Only parse strikethroughs if surrounded by exactly 2 tildes. * Gives some compatibility with redcarpet. */ #define CMARK_OPT_STRIKETHROUGH_DOUBLE_TILDE (1 << 14) /** Use style attributes to align table cells instead of align attributes. */ #define CMARK_OPT_TABLE_PREFER_STYLE_ATTRIBUTES (1 << 15) /** Include the remainder of the info string in code blocks in * a separate attribute. */ #define CMARK_OPT_FULL_INFO_STRING (1 << 16) /** Allow raw HTML and unsafe links, `javascript:`, `vbscript:`, `file:`, and * all `data:` URLs -- by default, only `image/png`, `image/gif`, `image/jpeg`, * or `image/webp` mime types are allowed. Without this option, raw HTML is * replaced by a placeholder HTML comment, and unsafe links are replaced by * empty strings. */ #define CMARK_OPT_UNSAFE (1 << 17) /** * ## Version information */ /** The library version as integer for runtime checks. Also available as * macro CMARK_VERSION for compile time checks. * * * Bits 16-23 contain the major version. * * Bits 8-15 contain the minor version. * * Bits 0-7 contain the patchlevel. * * In hexadecimal format, the number 0x010203 represents version 1.2.3. */ CMARK_GFM_EXPORT int cmark_version(void); /** The library version string for runtime checks. Also available as * macro CMARK_VERSION_STRING for compile time checks. */ CMARK_GFM_EXPORT const char *cmark_version_string(void); /** # AUTHORS * * John MacFarlane, Vicent Marti, Kārlis Gaņģis, Nick Wellnhofer. */ #ifndef CMARK_NO_SHORT_NAMES #define NODE_DOCUMENT CMARK_NODE_DOCUMENT #define NODE_BLOCK_QUOTE CMARK_NODE_BLOCK_QUOTE #define NODE_LIST CMARK_NODE_LIST #define NODE_ITEM CMARK_NODE_ITEM #define NODE_CODE_BLOCK CMARK_NODE_CODE_BLOCK #define NODE_HTML_BLOCK CMARK_NODE_HTML_BLOCK #define NODE_CUSTOM_BLOCK CMARK_NODE_CUSTOM_BLOCK #define NODE_PARAGRAPH CMARK_NODE_PARAGRAPH #define NODE_HEADING CMARK_NODE_HEADING #define NODE_HEADER CMARK_NODE_HEADER #define NODE_THEMATIC_BREAK CMARK_NODE_THEMATIC_BREAK #define NODE_HRULE CMARK_NODE_HRULE #define NODE_TEXT CMARK_NODE_TEXT #define NODE_SOFTBREAK CMARK_NODE_SOFTBREAK #define NODE_LINEBREAK CMARK_NODE_LINEBREAK #define NODE_CODE CMARK_NODE_CODE #define NODE_HTML_INLINE CMARK_NODE_HTML_INLINE #define NODE_CUSTOM_INLINE CMARK_NODE_CUSTOM_INLINE #define NODE_EMPH CMARK_NODE_EMPH #define NODE_STRONG CMARK_NODE_STRONG #define NODE_LINK CMARK_NODE_LINK #define NODE_IMAGE CMARK_NODE_IMAGE #define BULLET_LIST CMARK_BULLET_LIST #define ORDERED_LIST CMARK_ORDERED_LIST #define PERIOD_DELIM CMARK_PERIOD_DELIM #define PAREN_DELIM CMARK_PAREN_DELIM #endif typedef int32_t bufsize_t; #ifdef __cplusplus } #endif #endif �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/houdini.h���������������������������������������������������������������������0000644�0000000�0000000�00000003012�13442034251�014460� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_HOUDINI_H #define CMARK_HOUDINI_H #ifdef __cplusplus extern "C" { #endif #include <stdint.h> #include "config.h" #include "buffer.h" #ifdef HAVE___BUILTIN_EXPECT #define likely(x) __builtin_expect((x), 1) #define unlikely(x) __builtin_expect((x), 0) #else #define likely(x) (x) #define unlikely(x) (x) #endif #ifdef HOUDINI_USE_LOCALE #define _isxdigit(c) isxdigit(c) #define _isdigit(c) isdigit(c) #else /* * Helper _isdigit methods -- do not trust the current locale * */ #define _isxdigit(c) (strchr("0123456789ABCDEFabcdef", (c)) != NULL) #define _isdigit(c) ((c) >= '0' && (c) <= '9') #endif #define HOUDINI_ESCAPED_SIZE(x) (((x)*12) / 10) #define HOUDINI_UNESCAPED_SIZE(x) (x) CMARK_GFM_EXPORT bufsize_t houdini_unescape_ent(cmark_strbuf *ob, const uint8_t *src, bufsize_t size); CMARK_GFM_EXPORT int houdini_escape_html(cmark_strbuf *ob, const uint8_t *src, bufsize_t size); CMARK_GFM_EXPORT int houdini_escape_html0(cmark_strbuf *ob, const uint8_t *src, bufsize_t size, int secure); CMARK_GFM_EXPORT int houdini_unescape_html(cmark_strbuf *ob, const uint8_t *src, bufsize_t size); CMARK_GFM_EXPORT void houdini_unescape_html_f(cmark_strbuf *ob, const uint8_t *src, bufsize_t size); CMARK_GFM_EXPORT int houdini_escape_href(cmark_strbuf *ob, const uint8_t *src, bufsize_t size); #ifdef __cplusplus } #endif #endif ����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/references.h������������������������������������������������������������������0000644�0000000�0000000�00000000734�13442034251�015152� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_REFERENCES_H #define CMARK_REFERENCES_H #include "map.h" #ifdef __cplusplus extern "C" { #endif struct cmark_reference { cmark_map_entry entry; cmark_chunk url; cmark_chunk title; }; typedef struct cmark_reference cmark_reference; void cmark_reference_create(cmark_map *map, cmark_chunk *label, cmark_chunk *url, cmark_chunk *title); cmark_map *cmark_reference_map_new(cmark_mem *mem); #ifdef __cplusplus } #endif #endif ������������������������������������cmark-gfm-0.1.8/cbits/utf8.h������������������������������������������������������������������������0000644�0000000�0000000�00000001327�13442034251�013716� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_UTF8_H #define CMARK_UTF8_H #include <stdint.h> #include "buffer.h" #ifdef __cplusplus extern "C" { #endif CMARK_GFM_EXPORT void cmark_utf8proc_case_fold(cmark_strbuf *dest, const uint8_t *str, bufsize_t len); CMARK_GFM_EXPORT void cmark_utf8proc_encode_char(int32_t uc, cmark_strbuf *buf); CMARK_GFM_EXPORT int cmark_utf8proc_iterate(const uint8_t *str, bufsize_t str_len, int32_t *dst); CMARK_GFM_EXPORT void cmark_utf8proc_check(cmark_strbuf *dest, const uint8_t *line, bufsize_t size); CMARK_GFM_EXPORT int cmark_utf8proc_is_space(int32_t uc); CMARK_GFM_EXPORT int cmark_utf8proc_is_punctuation(int32_t uc); #ifdef __cplusplus } #endif #endif ���������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/parser.h����������������������������������������������������������������������0000644�0000000�0000000�00000003502�13442034251�014321� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_PARSER_H #define CMARK_PARSER_H #include <stdio.h> #include "node.h" #include "buffer.h" #include "memory.h" #ifdef __cplusplus extern "C" { #endif #define MAX_LINK_LABEL_LENGTH 1000 struct cmark_parser { struct cmark_mem *mem; /* A hashtable of urls in the current document for cross-references */ struct cmark_map *refmap; /* The root node of the parser, always a CMARK_NODE_DOCUMENT */ struct cmark_node *root; /* The last open block after a line is fully processed */ struct cmark_node *current; /* See the documentation for cmark_parser_get_line_number() in cmark.h */ int line_number; /* See the documentation for cmark_parser_get_offset() in cmark.h */ bufsize_t offset; /* See the documentation for cmark_parser_get_column() in cmark.h */ bufsize_t column; /* See the documentation for cmark_parser_get_first_nonspace() in cmark.h */ bufsize_t first_nonspace; /* See the documentation for cmark_parser_get_first_nonspace_column() in cmark.h */ bufsize_t first_nonspace_column; /* See the documentation for cmark_parser_get_indent() in cmark.h */ int indent; /* See the documentation for cmark_parser_is_blank() in cmark.h */ bool blank; /* See the documentation for cmark_parser_has_partially_consumed_tab() in cmark.h */ bool partially_consumed_tab; /* Contains the currently processed line */ cmark_strbuf curline; /* See the documentation for cmark_parser_get_last_line_length() in cmark.h */ bufsize_t last_line_length; /* FIXME: not sure about the difference with curline */ cmark_strbuf linebuf; /* Options set by the user, see the Options section in cmark.h */ int options; bool last_buffer_ended_with_cr; cmark_llist *syntax_extensions; cmark_llist *inline_syntax_extensions; cmark_ispunct_func backslash_ispunct; }; #ifdef __cplusplus } #endif #endif ����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/cmark-gfm_version.h�����������������������������������������������������������0000644�0000000�0000000�00000000265�13442037162�016445� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_VERSION_H #define CMARK_GFM_VERSION_H #define CMARK_GFM_VERSION ((0 << 24) | (28 << 16) | (3 << 8) | 20) #define CMARK_GFM_VERSION_STRING "0.28.3.gfm.20" #endif �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/html_unescape.h���������������������������������������������������������������0000644�0000000�0000000�00002267610�13315273412�015675� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������/* ANSI-C code produced by gperf version 3.0.3 */ /* Command-line: /Library/Developer/CommandLineTools/usr/bin/gperf -L ANSI-C -I -t -N find_entity -H hash_entity -K entity -C -l -F ',{0}' --null-strings -m5 -P -Q entity_pool src/html_unescape.gperf */ /* Computed positions: -k'1-7,10,12,$' */ #if !((' ' == 32) && ('!' == 33) && ('"' == 34) && ('#' == 35) \ && ('%' == 37) && ('&' == 38) && ('\'' == 39) && ('(' == 40) \ && (')' == 41) && ('*' == 42) && ('+' == 43) && (',' == 44) \ && ('-' == 45) && ('.' == 46) && ('/' == 47) && ('0' == 48) \ && ('1' == 49) && ('2' == 50) && ('3' == 51) && ('4' == 52) \ && ('5' == 53) && ('6' == 54) && ('7' == 55) && ('8' == 56) \ && ('9' == 57) && (':' == 58) && (';' == 59) && ('<' == 60) \ && ('=' == 61) && ('>' == 62) && ('?' == 63) && ('A' == 65) \ && ('B' == 66) && ('C' == 67) && ('D' == 68) && ('E' == 69) \ && ('F' == 70) && ('G' == 71) && ('H' == 72) && ('I' == 73) \ && ('J' == 74) && ('K' == 75) && ('L' == 76) && ('M' == 77) \ && ('N' == 78) && ('O' == 79) && ('P' == 80) && ('Q' == 81) \ && ('R' == 82) && ('S' == 83) && ('T' == 84) && ('U' == 85) \ && ('V' == 86) && ('W' == 87) && ('X' == 88) && ('Y' == 89) \ && ('Z' == 90) && ('[' == 91) && ('\\' == 92) && (']' == 93) \ && ('^' == 94) && ('_' == 95) && ('a' == 97) && ('b' == 98) \ && ('c' == 99) && ('d' == 100) && ('e' == 101) && ('f' == 102) \ && ('g' == 103) && ('h' == 104) && ('i' == 105) && ('j' == 106) \ && ('k' == 107) && ('l' == 108) && ('m' == 109) && ('n' == 110) \ && ('o' == 111) && ('p' == 112) && ('q' == 113) && ('r' == 114) \ && ('s' == 115) && ('t' == 116) && ('u' == 117) && ('v' == 118) \ && ('w' == 119) && ('x' == 120) && ('y' == 121) && ('z' == 122) \ && ('{' == 123) && ('|' == 124) && ('}' == 125) && ('~' == 126)) /* The character set is not based on ISO-646. */ #error "gperf generated tables don't work with this execution character set. Please report a bug to <bug-gnu-gperf@gnu.org>." #endif #line 1 "src/html_unescape.gperf" struct html_ent { int entity; unsigned char utf8[4]; }; #include <string.h> #include <stddef.h> #define TOTAL_KEYWORDS 2125 #define MIN_WORD_LENGTH 2 #define MAX_WORD_LENGTH 31 #define MIN_HASH_VALUE 39 #define MAX_HASH_VALUE 16000 /* maximum key range = 15962, duplicates = 0 */ #ifdef __GNUC__ __inline #else #ifdef __cplusplus inline #endif #endif static unsigned int hash_entity (register const char *str, register unsigned int len) { static const unsigned short asso_values[] = { 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 2, 3, 7, 2, 4, 8, 16001, 10, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 1890, 1538, 220, 165, 1045, 535, 1971, 1187, 1262, 35, 126, 201, 133, 350, 1487, 1965, 3, 478, 134, 8, 147, 73, 41, 23, 212, 9, 16001, 2, 16001, 2, 16001, 16001, 4154, 29, 3168, 429, 10, 146, 1925, 2307, 280, 1313, 1924, 4, 651, 27, 1031, 65, 176, 2, 6, 17, 15, 107, 482, 3207, 3865, 757, 131, 178, 4, 4, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001, 16001 }; register unsigned int hval = len; switch (hval) { default: hval += asso_values[(unsigned char)str[11]]; /*FALLTHROUGH*/ case 11: case 10: hval += asso_values[(unsigned char)str[9]]; /*FALLTHROUGH*/ case 9: case 8: case 7: hval += asso_values[(unsigned char)str[6]]; /*FALLTHROUGH*/ case 6: hval += asso_values[(unsigned char)str[5]]; /*FALLTHROUGH*/ case 5: hval += asso_values[(unsigned char)str[4]+1]; /*FALLTHROUGH*/ case 4: hval += asso_values[(unsigned char)str[3]+3]; /*FALLTHROUGH*/ case 3: hval += asso_values[(unsigned char)str[2]+1]; /*FALLTHROUGH*/ case 2: hval += asso_values[(unsigned char)str[1]+4]; /*FALLTHROUGH*/ case 1: hval += asso_values[(unsigned char)str[0]]; break; } return hval + asso_values[(unsigned char)str[len - 1]]; } struct entity_pool_t { char entity_pool_str39[sizeof("rarr")]; char entity_pool_str41[sizeof("larr")]; char entity_pool_str49[sizeof("lat")]; char entity_pool_str52[sizeof("uarr")]; char entity_pool_str55[sizeof("npr")]; char entity_pool_str62[sizeof("rarrtl")]; char entity_pool_str64[sizeof("larrtl")]; char entity_pool_str65[sizeof("roarr")]; char entity_pool_str67[sizeof("loarr")]; char entity_pool_str68[sizeof("not")]; char entity_pool_str69[sizeof("rpar")]; char entity_pool_str70[sizeof("bot")]; char entity_pool_str71[sizeof("lpar")]; char entity_pool_str73[sizeof("spar")]; char entity_pool_str75[sizeof("ll")]; char entity_pool_str76[sizeof("uharr")]; char entity_pool_str77[sizeof("epar")]; char entity_pool_str81[sizeof("el")]; char entity_pool_str83[sizeof("rotimes")]; char entity_pool_str85[sizeof("lotimes")]; char entity_pool_str86[sizeof("par")]; char entity_pool_str88[sizeof("nharr")]; char entity_pool_str94[sizeof("npar")]; char entity_pool_str97[sizeof("tprime")]; char entity_pool_str101[sizeof("els")]; char entity_pool_str102[sizeof("eparsl")]; char entity_pool_str104[sizeof("ensp")]; char entity_pool_str109[sizeof("bprime")]; char entity_pool_str110[sizeof("lnap")]; char entity_pool_str111[sizeof("blk14")]; char entity_pool_str115[sizeof("blk12")]; char entity_pool_str117[sizeof("blk34")]; char entity_pool_str119[sizeof("nparsl")]; char entity_pool_str123[sizeof("nldr")]; char entity_pool_str124[sizeof("rlarr")]; char entity_pool_str125[sizeof("npart")]; char entity_pool_str126[sizeof("llarr")]; char entity_pool_str127[sizeof("nlt")]; char entity_pool_str128[sizeof("slarr")]; char entity_pool_str138[sizeof("nparallel")]; char entity_pool_str143[sizeof("Tau")]; char entity_pool_str144[sizeof("varr")]; char entity_pool_str146[sizeof("squ")]; char entity_pool_str149[sizeof("nlarr")]; char entity_pool_str152[sizeof("tau")]; char entity_pool_str165[sizeof("lne")]; char entity_pool_str166[sizeof("rrarr")]; char entity_pool_str168[sizeof("lrarr")]; char entity_pool_str170[sizeof("srarr")]; char entity_pool_str171[sizeof("rharul")]; char entity_pool_str173[sizeof("lharul")]; char entity_pool_str174[sizeof("erarr")]; char entity_pool_str176[sizeof("pr")]; char entity_pool_str177[sizeof("rharu")]; char entity_pool_str179[sizeof("lharu")]; char entity_pool_str184[sizeof("Uarr")]; char entity_pool_str188[sizeof("nGt")]; char entity_pool_str190[sizeof("bne")]; char entity_pool_str191[sizeof("nrarr")]; char entity_pool_str194[sizeof("swarr")]; char entity_pool_str198[sizeof("rarrap")]; char entity_pool_str200[sizeof("upuparrows")]; char entity_pool_str202[sizeof("Darr")]; char entity_pool_str205[sizeof("rbarr")]; char entity_pool_str206[sizeof("Dot")]; char entity_pool_str207[sizeof("lbarr")]; char entity_pool_str215[sizeof("nwarr")]; char entity_pool_str217[sizeof("smt")]; char entity_pool_str222[sizeof("emsp14")]; char entity_pool_str223[sizeof("rarrpl")]; char entity_pool_str225[sizeof("larrpl")]; char entity_pool_str230[sizeof("phmmat")]; char entity_pool_str232[sizeof("emsp13")]; char entity_pool_str234[sizeof("LT")]; char entity_pool_str238[sizeof("Larr")]; char entity_pool_str239[sizeof("rbrkslu")]; char entity_pool_str241[sizeof("lbrkslu")]; char entity_pool_str243[sizeof("napos")]; char entity_pool_str251[sizeof("nle")]; char entity_pool_str253[sizeof("rHar")]; char entity_pool_str255[sizeof("lHar")]; char entity_pool_str256[sizeof("qprime")]; char entity_pool_str258[sizeof("lap")]; char entity_pool_str265[sizeof("nbsp")]; char entity_pool_str266[sizeof("uHar")]; char entity_pool_str267[sizeof("top")]; char entity_pool_str269[sizeof("Vbar")]; char entity_pool_str272[sizeof("Ll")]; char entity_pool_str276[sizeof("prap")]; char entity_pool_str278[sizeof("emsp")]; char entity_pool_str281[sizeof("nap")]; char entity_pool_str294[sizeof("looparrowleft")]; char entity_pool_str296[sizeof("le")]; char entity_pool_str300[sizeof("sharp")]; char entity_pool_str302[sizeof("ee")]; char entity_pool_str310[sizeof("les")]; char entity_pool_str311[sizeof("in")]; char entity_pool_str312[sizeof("prop")]; char entity_pool_str314[sizeof("topbot")]; char entity_pool_str317[sizeof("int")]; char entity_pool_str319[sizeof("ne")]; char entity_pool_str329[sizeof("nprcue")]; char entity_pool_str331[sizeof("pre")]; char entity_pool_str332[sizeof("epsi")]; char entity_pool_str337[sizeof("upsi")]; char entity_pool_str338[sizeof("there4")]; char entity_pool_str342[sizeof("rbrke")]; char entity_pool_str343[sizeof("searr")]; char entity_pool_str344[sizeof("lbrke")]; char entity_pool_str346[sizeof("blacktriangle")]; char entity_pool_str349[sizeof("lneq")]; char entity_pool_str352[sizeof("lneqq")]; char entity_pool_str354[sizeof("plus")]; char entity_pool_str355[sizeof("nles")]; char entity_pool_str356[sizeof("nedot")]; char entity_pool_str357[sizeof("blacktriangleleft")]; char entity_pool_str358[sizeof("blacktriangleright")]; char entity_pool_str364[sizeof("nearr")]; char entity_pool_str367[sizeof("blacktriangledown")]; char entity_pool_str373[sizeof("nless")]; char entity_pool_str374[sizeof("emacr")]; char entity_pool_str378[sizeof("vprop")]; char entity_pool_str379[sizeof("umacr")]; char entity_pool_str383[sizeof("smeparsl")]; char entity_pool_str387[sizeof("Map")]; char entity_pool_str390[sizeof("plusdu")]; char entity_pool_str391[sizeof("Not")]; char entity_pool_str408[sizeof("Verbar")]; char entity_pool_str426[sizeof("perp")]; char entity_pool_str430[sizeof("fltns")]; char entity_pool_str431[sizeof("plusmn")]; char entity_pool_str435[sizeof("nleq")]; char entity_pool_str438[sizeof("nleqq")]; char entity_pool_str440[sizeof("frac34")]; char entity_pool_str441[sizeof("frac14")]; char entity_pool_str442[sizeof("verbar")]; char entity_pool_str443[sizeof("frac12")]; char entity_pool_str444[sizeof("frac35")]; char entity_pool_str445[sizeof("frac15")]; char entity_pool_str446[sizeof("frac45")]; char entity_pool_str449[sizeof("frac25")]; char entity_pool_str451[sizeof("frac13")]; char entity_pool_str453[sizeof("frac16")]; char entity_pool_str454[sizeof("prurel")]; char entity_pool_str455[sizeof("frac23")]; char entity_pool_str456[sizeof("frac38")]; char entity_pool_str457[sizeof("frac18")]; char entity_pool_str458[sizeof("frac56")]; char entity_pool_str462[sizeof("frac58")]; char entity_pool_str464[sizeof("frac78")]; char entity_pool_str465[sizeof("leq")]; char entity_pool_str466[sizeof("darr")]; char entity_pool_str469[sizeof("Upsi")]; char entity_pool_str470[sizeof("dot")]; char entity_pool_str471[sizeof("phone")]; char entity_pool_str474[sizeof("Cap")]; char entity_pool_str478[sizeof("blacksquare")]; char entity_pool_str479[sizeof("rnmid")]; char entity_pool_str483[sizeof("leqq")]; char entity_pool_str486[sizeof("intcal")]; char entity_pool_str490[sizeof("dharr")]; char entity_pool_str494[sizeof("rhard")]; char entity_pool_str496[sizeof("lhard")]; char entity_pool_str505[sizeof("pluse")]; char entity_pool_str511[sizeof("Umacr")]; char entity_pool_str512[sizeof("Vee")]; char entity_pool_str515[sizeof("Rarr")]; char entity_pool_str527[sizeof("Cross")]; char entity_pool_str529[sizeof("rsqb")]; char entity_pool_str531[sizeof("lsqb")]; char entity_pool_str538[sizeof("Rarrtl")]; char entity_pool_str541[sizeof("esdot")]; char entity_pool_str546[sizeof("vee")]; char entity_pool_str547[sizeof("nbumpe")]; char entity_pool_str553[sizeof("llcorner")]; char entity_pool_str554[sizeof("fpartint")]; char entity_pool_str558[sizeof("squf")]; char entity_pool_str559[sizeof("plankv")]; char entity_pool_str562[sizeof("eqvparsl")]; char entity_pool_str564[sizeof("ulcorner")]; char entity_pool_str566[sizeof("wp")]; char entity_pool_str571[sizeof("lozf")]; char entity_pool_str575[sizeof("COPY")]; char entity_pool_str577[sizeof("ulcorn")]; char entity_pool_str582[sizeof("veebar")]; char entity_pool_str584[sizeof("part")]; char entity_pool_str589[sizeof("square")]; char entity_pool_str591[sizeof("nbump")]; char entity_pool_str592[sizeof("bernou")]; char entity_pool_str593[sizeof("wr")]; char entity_pool_str594[sizeof("rBarr")]; char entity_pool_str595[sizeof("lrcorner")]; char entity_pool_str596[sizeof("lBarr")]; char entity_pool_str599[sizeof("bnot")]; char entity_pool_str601[sizeof("semi")]; char entity_pool_str606[sizeof("urcorner")]; char entity_pool_str612[sizeof("NotSubset")]; char entity_pool_str614[sizeof("ropf")]; char entity_pool_str615[sizeof("Qopf")]; char entity_pool_str616[sizeof("lopf")]; char entity_pool_str618[sizeof("sopf")]; char entity_pool_str619[sizeof("urcorn")]; char entity_pool_str620[sizeof("Topf")]; char entity_pool_str621[sizeof("Zopf")]; char entity_pool_str622[sizeof("eopf")]; char entity_pool_str626[sizeof("ropar")]; char entity_pool_str627[sizeof("uopf")]; char entity_pool_str628[sizeof("lopar")]; char entity_pool_str629[sizeof("topf")]; char entity_pool_str635[sizeof("Xopf")]; char entity_pool_str639[sizeof("nopf")]; char entity_pool_str641[sizeof("bopf")]; char entity_pool_str642[sizeof("epsiv")]; char entity_pool_str643[sizeof("fnof")]; char entity_pool_str644[sizeof("imacr")]; char entity_pool_str647[sizeof("Jopf")]; char entity_pool_str649[sizeof("nhpar")]; char entity_pool_str653[sizeof("Wopf")]; char entity_pool_str658[sizeof("Sqrt")]; char entity_pool_str659[sizeof("nsub")]; char entity_pool_str661[sizeof("napid")]; char entity_pool_str664[sizeof("NotSuperset")]; char entity_pool_str667[sizeof("brvbar")]; char entity_pool_str670[sizeof("sol")]; char entity_pool_str675[sizeof("easter")]; char entity_pool_str677[sizeof("popf")]; char entity_pool_str680[sizeof("dHar")]; char entity_pool_str685[sizeof("Vopf")]; char entity_pool_str690[sizeof("nsupset")]; char entity_pool_str691[sizeof("nsup")]; char entity_pool_str692[sizeof("vBar")]; char entity_pool_str694[sizeof("nsubset")]; char entity_pool_str700[sizeof("thkap")]; char entity_pool_str704[sizeof("nis")]; char entity_pool_str705[sizeof("profsurf")]; char entity_pool_str706[sizeof("solb")]; char entity_pool_str710[sizeof("lnsim")]; char entity_pool_str712[sizeof("solbar")]; char entity_pool_str717[sizeof("Square")]; char entity_pool_str719[sizeof("vopf")]; char entity_pool_str723[sizeof("uharl")]; char entity_pool_str725[sizeof("ulcrop")]; char entity_pool_str729[sizeof("eqsim")]; char entity_pool_str730[sizeof("equiv")]; char entity_pool_str733[sizeof("ell")]; char entity_pool_str734[sizeof("smashp")]; char entity_pool_str735[sizeof("mp")]; char entity_pool_str738[sizeof("Kopf")]; char entity_pool_str741[sizeof("simrarr")]; char entity_pool_str743[sizeof("flat")]; char entity_pool_str745[sizeof("Mopf")]; char entity_pool_str746[sizeof("Sopf")]; char entity_pool_str747[sizeof("mldr")]; char entity_pool_str748[sizeof("rlm")]; char entity_pool_str749[sizeof("iprod")]; char entity_pool_str756[sizeof("lparlt")]; char entity_pool_str758[sizeof("fopf")]; char entity_pool_str759[sizeof("Uopf")]; char entity_pool_str763[sizeof("varsubsetneq")]; char entity_pool_str764[sizeof("varsubsetneqq")]; char entity_pool_str767[sizeof("urcrop")]; char entity_pool_str768[sizeof("LessLess")]; char entity_pool_str770[sizeof("Re")]; char entity_pool_str773[sizeof("NotNestedLessLess")]; char entity_pool_str777[sizeof("Dopf")]; char entity_pool_str779[sizeof("forkv")]; char entity_pool_str781[sizeof("nsqsube")]; char entity_pool_str783[sizeof("nsupe")]; char entity_pool_str787[sizeof("nsube")]; char entity_pool_str788[sizeof("qopf")]; char entity_pool_str789[sizeof("rlhar")]; char entity_pool_str792[sizeof("lrm")]; char entity_pool_str796[sizeof("nlsim")]; char entity_pool_str798[sizeof("pound")]; char entity_pool_str799[sizeof("varsupsetneq")]; char entity_pool_str800[sizeof("varsupsetneqq")]; char entity_pool_str802[sizeof("bnequiv")]; char entity_pool_str813[sizeof("Lopf")]; char entity_pool_str817[sizeof("nsqsupe")]; char entity_pool_str820[sizeof("rarrlp")]; char entity_pool_str821[sizeof("wedbar")]; char entity_pool_str822[sizeof("larrlp")]; char entity_pool_str824[sizeof("Yopf")]; char entity_pool_str829[sizeof("NotReverseElement")]; char entity_pool_str832[sizeof("Copf")]; char entity_pool_str833[sizeof("lrhar")]; char entity_pool_str848[sizeof("parsl")]; char entity_pool_str849[sizeof("uml")]; char entity_pool_str850[sizeof("marker")]; char entity_pool_str851[sizeof("nsupseteq")]; char entity_pool_str855[sizeof("nsubseteq")]; char entity_pool_str861[sizeof("squarf")]; char entity_pool_str862[sizeof("Vert")]; char entity_pool_str874[sizeof("SquareSupersetEqual")]; char entity_pool_str876[sizeof("prsim")]; char entity_pool_str879[sizeof("SquareSubsetEqual")]; char entity_pool_str882[sizeof("SquareSuperset")]; char entity_pool_str887[sizeof("SquareSubset")]; char entity_pool_str888[sizeof("nvap")]; char entity_pool_str892[sizeof("iopf")]; char entity_pool_str894[sizeof("pm")]; char entity_pool_str896[sizeof("vert")]; char entity_pool_str898[sizeof("thetav")]; char entity_pool_str901[sizeof("loz")]; char entity_pool_str905[sizeof("map")]; char entity_pool_str920[sizeof("lesseqqgtr")]; char entity_pool_str934[sizeof("rscr")]; char entity_pool_str935[sizeof("Qscr")]; char entity_pool_str936[sizeof("lscr")]; char entity_pool_str938[sizeof("sscr")]; char entity_pool_str940[sizeof("Tscr")]; char entity_pool_str941[sizeof("Zscr")]; char entity_pool_str942[sizeof("escr")]; char entity_pool_str947[sizeof("uscr")]; char entity_pool_str949[sizeof("tscr")]; char entity_pool_str951[sizeof("imof")]; char entity_pool_str952[sizeof("Coproduct")]; char entity_pool_str955[sizeof("Xscr")]; char entity_pool_str956[sizeof("Xi")]; char entity_pool_str959[sizeof("nscr")]; char entity_pool_str960[sizeof("ni")]; char entity_pool_str961[sizeof("bscr")]; char entity_pool_str962[sizeof("Nopf")]; char entity_pool_str967[sizeof("Jscr")]; char entity_pool_str968[sizeof("preceq")]; char entity_pool_str971[sizeof("nvrArr")]; char entity_pool_str972[sizeof("backprime")]; char entity_pool_str973[sizeof("Wscr")]; char entity_pool_str975[sizeof("varphi")]; char entity_pool_str984[sizeof("nsmid")]; char entity_pool_str991[sizeof("dlcorn")]; char entity_pool_str997[sizeof("pscr")]; char entity_pool_str998[sizeof("pi")]; char entity_pool_str1005[sizeof("Vscr")]; char entity_pool_str1011[sizeof("nesim")]; char entity_pool_str1021[sizeof("simne")]; char entity_pool_str1028[sizeof("nsupseteqq")]; char entity_pool_str1032[sizeof("nsubseteqq")]; char entity_pool_str1033[sizeof("drcorn")]; char entity_pool_str1038[sizeof("rbrace")]; char entity_pool_str1039[sizeof("vscr")]; char entity_pool_str1040[sizeof("lbrace")]; char entity_pool_str1041[sizeof("dopf")]; char entity_pool_str1049[sizeof("frasl")]; char entity_pool_str1055[sizeof("LessTilde")]; char entity_pool_str1058[sizeof("Kscr")]; char entity_pool_str1064[sizeof("pluscir")]; char entity_pool_str1065[sizeof("Mscr")]; char entity_pool_str1066[sizeof("Sscr")]; char entity_pool_str1067[sizeof("rbrksld")]; char entity_pool_str1069[sizeof("lbrksld")]; char entity_pool_str1070[sizeof("RBarr")]; char entity_pool_str1073[sizeof("sqcaps")]; char entity_pool_str1074[sizeof("rArr")]; char entity_pool_str1075[sizeof("bNot")]; char entity_pool_str1076[sizeof("lArr")]; char entity_pool_str1078[sizeof("fscr")]; char entity_pool_str1079[sizeof("Uscr")]; char entity_pool_str1087[sizeof("uArr")]; char entity_pool_str1090[sizeof("Ropf")]; char entity_pool_str1094[sizeof("wopf")]; char entity_pool_str1097[sizeof("Dscr")]; char entity_pool_str1098[sizeof("opar")]; char entity_pool_str1099[sizeof("seswar")]; char entity_pool_str1103[sizeof("Del")]; char entity_pool_str1104[sizeof("rAarr")]; char entity_pool_str1105[sizeof("rho")]; char entity_pool_str1106[sizeof("lAarr")]; char entity_pool_str1107[sizeof("preccurlyeq")]; char entity_pool_str1108[sizeof("qscr")]; char entity_pool_str1111[sizeof("macr")]; char entity_pool_str1115[sizeof("notin")]; char entity_pool_str1120[sizeof("equivDD")]; char entity_pool_str1125[sizeof("sqcap")]; char entity_pool_str1127[sizeof("nspar")]; char entity_pool_str1131[sizeof("olt")]; char entity_pool_str1132[sizeof("ratio")]; char entity_pool_str1133[sizeof("Lscr")]; char entity_pool_str1137[sizeof("dharl")]; char entity_pool_str1139[sizeof("dlcrop")]; char entity_pool_str1140[sizeof("DoubleDot")]; char entity_pool_str1141[sizeof("dotplus")]; char entity_pool_str1142[sizeof("or")]; char entity_pool_str1144[sizeof("Yscr")]; char entity_pool_str1147[sizeof("Fopf")]; char entity_pool_str1152[sizeof("Cscr")]; char entity_pool_str1153[sizeof("olarr")]; char entity_pool_str1154[sizeof("nrarrw")]; char entity_pool_str1159[sizeof("lvertneqq")]; char entity_pool_str1160[sizeof("eqslantgtr")]; char entity_pool_str1164[sizeof("thorn")]; char entity_pool_str1169[sizeof("eqslantless")]; char entity_pool_str1172[sizeof("incare")]; char entity_pool_str1179[sizeof("vArr")]; char entity_pool_str1180[sizeof("rppolint")]; char entity_pool_str1181[sizeof("drcrop")]; char entity_pool_str1187[sizeof("parallel")]; char entity_pool_str1195[sizeof("orarr")]; char entity_pool_str1196[sizeof("ssmile")]; char entity_pool_str1200[sizeof("DoubleLeftTee")]; char entity_pool_str1201[sizeof("erDot")]; char entity_pool_str1202[sizeof("diams")]; char entity_pool_str1203[sizeof("ssetmn")]; char entity_pool_str1208[sizeof("oS")]; char entity_pool_str1212[sizeof("iscr")]; char entity_pool_str1213[sizeof("ii")]; char entity_pool_str1214[sizeof("rect")]; char entity_pool_str1217[sizeof("nsccue")]; char entity_pool_str1218[sizeof("sect")]; char entity_pool_str1220[sizeof("mlcp")]; char entity_pool_str1224[sizeof("oror")]; char entity_pool_str1226[sizeof("DoubleContourIntegral")]; char entity_pool_str1230[sizeof("equals")]; char entity_pool_str1232[sizeof("Hat")]; char entity_pool_str1236[sizeof("sstarf")]; char entity_pool_str1237[sizeof("mstpos")]; char entity_pool_str1239[sizeof("die")]; char entity_pool_str1240[sizeof("measuredangle")]; char entity_pool_str1252[sizeof("forall")]; char entity_pool_str1255[sizeof("notinvb")]; char entity_pool_str1263[sizeof("mopf")]; char entity_pool_str1270[sizeof("niv")]; char entity_pool_str1280[sizeof("vBarv")]; char entity_pool_str1282[sizeof("Nscr")]; char entity_pool_str1284[sizeof("period")]; char entity_pool_str1292[sizeof("becaus")]; char entity_pool_str1298[sizeof("between")]; char entity_pool_str1299[sizeof("Int")]; char entity_pool_str1307[sizeof("because")]; char entity_pool_str1308[sizeof("piv")]; char entity_pool_str1326[sizeof("rfr")]; char entity_pool_str1327[sizeof("Qfr")]; char entity_pool_str1328[sizeof("lfr")]; char entity_pool_str1330[sizeof("sfr")]; char entity_pool_str1331[sizeof("nleftrightarrow")]; char entity_pool_str1332[sizeof("Tfr")]; char entity_pool_str1333[sizeof("Zfr")]; char entity_pool_str1334[sizeof("efr")]; char entity_pool_str1338[sizeof("sim")]; char entity_pool_str1339[sizeof("ufr")]; char entity_pool_str1340[sizeof("roplus")]; char entity_pool_str1341[sizeof("tfr")]; char entity_pool_str1342[sizeof("loplus")]; char entity_pool_str1347[sizeof("Xfr")]; char entity_pool_str1350[sizeof("real")]; char entity_pool_str1351[sizeof("nfr")]; char entity_pool_str1353[sizeof("bfr")]; char entity_pool_str1355[sizeof("NotHumpEqual")]; char entity_pool_str1359[sizeof("Jfr")]; char entity_pool_str1361[sizeof("dscr")]; char entity_pool_str1365[sizeof("Wfr")]; char entity_pool_str1367[sizeof("blacklozenge")]; char entity_pool_str1369[sizeof("zopf")]; char entity_pool_str1370[sizeof("reals")]; char entity_pool_str1372[sizeof("NotCupCap")]; char entity_pool_str1375[sizeof("simplus")]; char entity_pool_str1377[sizeof("ForAll")]; char entity_pool_str1389[sizeof("pfr")]; char entity_pool_str1395[sizeof("omacr")]; char entity_pool_str1397[sizeof("Vfr")]; char entity_pool_str1409[sizeof("Emacr")]; char entity_pool_str1410[sizeof("Rscr")]; char entity_pool_str1414[sizeof("wscr")]; char entity_pool_str1423[sizeof("ShortUpArrow")]; char entity_pool_str1429[sizeof("setmn")]; char entity_pool_str1431[sizeof("vfr")]; char entity_pool_str1450[sizeof("Kfr")]; char entity_pool_str1455[sizeof("operp")]; char entity_pool_str1457[sizeof("Mfr")]; char entity_pool_str1458[sizeof("Sfr")]; char entity_pool_str1461[sizeof("nltrie")]; char entity_pool_str1467[sizeof("Fscr")]; char entity_pool_str1470[sizeof("ffr")]; char entity_pool_str1471[sizeof("Ufr")]; char entity_pool_str1473[sizeof("shortmid")]; char entity_pool_str1488[sizeof("nvsim")]; char entity_pool_str1489[sizeof("Dfr")]; char entity_pool_str1490[sizeof("lessdot")]; char entity_pool_str1493[sizeof("profline")]; char entity_pool_str1500[sizeof("qfr")]; char entity_pool_str1501[sizeof("dArr")]; char entity_pool_str1503[sizeof("nrtrie")]; char entity_pool_str1507[sizeof("ShortRightArrow")]; char entity_pool_str1515[sizeof("Therefore")]; char entity_pool_str1519[sizeof("DD")]; char entity_pool_str1524[sizeof("therefore")]; char entity_pool_str1525[sizeof("Lfr")]; char entity_pool_str1532[sizeof("target")]; char entity_pool_str1535[sizeof("Element")]; char entity_pool_str1536[sizeof("Yfr")]; char entity_pool_str1537[sizeof("ClockwiseContourIntegral")]; char entity_pool_str1542[sizeof("olcir")]; char entity_pool_str1544[sizeof("Cfr")]; char entity_pool_str1559[sizeof("female")]; char entity_pool_str1560[sizeof("nsucceq")]; char entity_pool_str1561[sizeof("oast")]; char entity_pool_str1568[sizeof("percnt")]; char entity_pool_str1578[sizeof("ordf")]; char entity_pool_str1580[sizeof("ord")]; char entity_pool_str1581[sizeof("Rho")]; char entity_pool_str1583[sizeof("mscr")]; char entity_pool_str1585[sizeof("nvrtrie")]; char entity_pool_str1589[sizeof("lnE")]; char entity_pool_str1597[sizeof("nhArr")]; char entity_pool_str1598[sizeof("Or")]; char entity_pool_str1602[sizeof("divide")]; char entity_pool_str1604[sizeof("ifr")]; char entity_pool_str1605[sizeof("elinters")]; char entity_pool_str1615[sizeof("bsol")]; char entity_pool_str1616[sizeof("nvlArr")]; char entity_pool_str1626[sizeof("Imacr")]; char entity_pool_str1628[sizeof("backsimeq")]; char entity_pool_str1629[sizeof("twixt")]; char entity_pool_str1630[sizeof("olcross")]; char entity_pool_str1639[sizeof("rarrsim")]; char entity_pool_str1640[sizeof("DoubleDownArrow")]; char entity_pool_str1641[sizeof("larrsim")]; char entity_pool_str1642[sizeof("emptyset")]; char entity_pool_str1643[sizeof("oopf")]; char entity_pool_str1645[sizeof("exist")]; char entity_pool_str1648[sizeof("llhard")]; char entity_pool_str1656[sizeof("excl")]; char entity_pool_str1657[sizeof("Eopf")]; char entity_pool_str1658[sizeof("nlArr")]; char entity_pool_str1663[sizeof("thinsp")]; char entity_pool_str1664[sizeof("NotSubsetEqual")]; char entity_pool_str1665[sizeof("phi")]; char entity_pool_str1666[sizeof("DoubleLeftArrow")]; char entity_pool_str1668[sizeof("topcir")]; char entity_pool_str1672[sizeof("div")]; char entity_pool_str1674[sizeof("Nfr")]; char entity_pool_str1675[sizeof("nlE")]; char entity_pool_str1689[sizeof("zscr")]; char entity_pool_str1690[sizeof("lrhard")]; char entity_pool_str1697[sizeof("lltri")]; char entity_pool_str1700[sizeof("nrArr")]; char entity_pool_str1701[sizeof("NotSupersetEqual")]; char entity_pool_str1703[sizeof("swArr")]; char entity_pool_str1704[sizeof("ThickSpace")]; char entity_pool_str1708[sizeof("ultri")]; char entity_pool_str1709[sizeof("notnivb")]; char entity_pool_str1711[sizeof("prime")]; char entity_pool_str1714[sizeof("primes")]; char entity_pool_str1716[sizeof("ohm")]; char entity_pool_str1719[sizeof("CircleTimes")]; char entity_pool_str1720[sizeof("nltri")]; char entity_pool_str1723[sizeof("siml")]; char entity_pool_str1724[sizeof("nwArr")]; char entity_pool_str1727[sizeof("varpi")]; char entity_pool_str1730[sizeof("orv")]; char entity_pool_str1735[sizeof("setminus")]; char entity_pool_str1739[sizeof("lrtri")]; char entity_pool_str1743[sizeof("permil")]; char entity_pool_str1744[sizeof("mid")]; char entity_pool_str1750[sizeof("urtri")]; char entity_pool_str1753[sizeof("dfr")]; char entity_pool_str1754[sizeof("mho")]; char entity_pool_str1755[sizeof("prE")]; char entity_pool_str1759[sizeof("vsupne")]; char entity_pool_str1762[sizeof("nrtri")]; char entity_pool_str1763[sizeof("vsubne")]; char entity_pool_str1765[sizeof("eDot")]; char entity_pool_str1778[sizeof("lesges")]; char entity_pool_str1781[sizeof("backepsilon")]; char entity_pool_str1783[sizeof("ratail")]; char entity_pool_str1785[sizeof("latail")]; char entity_pool_str1788[sizeof("UpEquilibrium")]; char entity_pool_str1791[sizeof("epsilon")]; char entity_pool_str1796[sizeof("upsilon")]; char entity_pool_str1798[sizeof("midast")]; char entity_pool_str1799[sizeof("Hopf")]; char entity_pool_str1800[sizeof("vltri")]; char entity_pool_str1802[sizeof("Rfr")]; char entity_pool_str1805[sizeof("Wedge")]; char entity_pool_str1806[sizeof("wfr")]; char entity_pool_str1812[sizeof("barwed")]; char entity_pool_str1815[sizeof("malt")]; char entity_pool_str1820[sizeof("Chi")]; char entity_pool_str1821[sizeof("emptyv")]; char entity_pool_str1822[sizeof("notni")]; char entity_pool_str1827[sizeof("LessGreater")]; char entity_pool_str1829[sizeof("diam")]; char entity_pool_str1842[sizeof("vrtri")]; char entity_pool_str1849[sizeof("CircleMinus")]; char entity_pool_str1851[sizeof("Omacr")]; char entity_pool_str1852[sizeof("seArr")]; char entity_pool_str1859[sizeof("Ffr")]; char entity_pool_str1865[sizeof("precneqq")]; char entity_pool_str1867[sizeof("Diamond")]; char entity_pool_str1868[sizeof("ordm")]; char entity_pool_str1873[sizeof("neArr")]; char entity_pool_str1874[sizeof("Iopf")]; char entity_pool_str1875[sizeof("CircleDot")]; char entity_pool_str1878[sizeof("prnap")]; char entity_pool_str1884[sizeof("dotminus")]; char entity_pool_str1903[sizeof("nshortmid")]; char entity_pool_str1905[sizeof("bottom")]; char entity_pool_str1907[sizeof("pointint")]; char entity_pool_str1917[sizeof("SquareUnion")]; char entity_pool_str1925[sizeof("jopf")]; char entity_pool_str1928[sizeof("Upsilon")]; char entity_pool_str1936[sizeof("Colone")]; char entity_pool_str1938[sizeof("nvlt")]; char entity_pool_str1941[sizeof("NestedLessLess")]; char entity_pool_str1942[sizeof("Colon")]; char entity_pool_str1945[sizeof("bsolhsub")]; char entity_pool_str1949[sizeof("DoubleLeftRightArrow")]; char entity_pool_str1950[sizeof("plussim")]; char entity_pool_str1959[sizeof("image")]; char entity_pool_str1960[sizeof("egs")]; char entity_pool_str1963[sizeof("oscr")]; char entity_pool_str1964[sizeof("swnwar")]; char entity_pool_str1969[sizeof("zeetrf")]; char entity_pool_str1973[sizeof("maltese")]; char entity_pool_str1975[sizeof("mfr")]; char entity_pool_str1976[sizeof("rarrfs")]; char entity_pool_str1977[sizeof("Escr")]; char entity_pool_str1978[sizeof("larrfs")]; char entity_pool_str1985[sizeof("mnplus")]; char entity_pool_str1986[sizeof("ngt")]; char entity_pool_str1987[sizeof("ngtr")]; char entity_pool_str1996[sizeof("gl")]; char entity_pool_str2003[sizeof("diamondsuit")]; char entity_pool_str2004[sizeof("GT")]; char entity_pool_str2014[sizeof("lesssim")]; char entity_pool_str2015[sizeof("dsol")]; char entity_pool_str2023[sizeof("upharpoonleft")]; char entity_pool_str2024[sizeof("SquareIntersection")]; char entity_pool_str2025[sizeof("lsime")]; char entity_pool_str2027[sizeof("nLt")]; char entity_pool_str2029[sizeof("NotLess")]; char entity_pool_str2031[sizeof("gnap")]; char entity_pool_str2035[sizeof("scap")]; char entity_pool_str2038[sizeof("mapstoleft")]; char entity_pool_str2039[sizeof("NotLessLess")]; char entity_pool_str2043[sizeof("rfloor")]; char entity_pool_str2045[sizeof("lfloor")]; char entity_pool_str2048[sizeof("nsime")]; char entity_pool_str2050[sizeof("bsime")]; char entity_pool_str2051[sizeof("NotLessEqual")]; char entity_pool_str2052[sizeof("NotLessTilde")]; char entity_pool_str2056[sizeof("ncap")]; char entity_pool_str2059[sizeof("NotLessGreater")]; char entity_pool_str2070[sizeof("precsim")]; char entity_pool_str2072[sizeof("looparrowright")]; char entity_pool_str2076[sizeof("Pr")]; char entity_pool_str2077[sizeof("rcub")]; char entity_pool_str2078[sizeof("mapstoup")]; char entity_pool_str2079[sizeof("lcub")]; char entity_pool_str2081[sizeof("zfr")]; char entity_pool_str2084[sizeof("uparrow")]; char entity_pool_str2086[sizeof("gne")]; char entity_pool_str2090[sizeof("sce")]; char entity_pool_str2091[sizeof("Im")]; char entity_pool_str2096[sizeof("rcaron")]; char entity_pool_str2098[sizeof("lcaron")]; char entity_pool_str2099[sizeof("Oopf")]; char entity_pool_str2100[sizeof("scaron")]; char entity_pool_str2101[sizeof("backsim")]; char entity_pool_str2102[sizeof("Tcaron")]; char entity_pool_str2103[sizeof("Zcaron")]; char entity_pool_str2104[sizeof("ecaron")]; char entity_pool_str2106[sizeof("Bernoullis")]; char entity_pool_str2110[sizeof("nge")]; char entity_pool_str2111[sizeof("tcaron")]; char entity_pool_str2113[sizeof("fork")]; char entity_pool_str2119[sizeof("Hscr")]; char entity_pool_str2121[sizeof("ncaron")]; char entity_pool_str2122[sizeof("elsdot")]; char entity_pool_str2124[sizeof("tbrk")]; char entity_pool_str2128[sizeof("triplus")]; char entity_pool_str2131[sizeof("diamond")]; char entity_pool_str2134[sizeof("ncup")]; char entity_pool_str2136[sizeof("bbrk")]; char entity_pool_str2138[sizeof("frown")]; char entity_pool_str2139[sizeof("bkarow")]; char entity_pool_str2141[sizeof("spades")]; char entity_pool_str2143[sizeof("psi")]; char entity_pool_str2150[sizeof("Bopf")]; char entity_pool_str2156[sizeof("dollar")]; char entity_pool_str2164[sizeof("disin")]; char entity_pool_str2170[sizeof("spadesuit")]; char entity_pool_str2176[sizeof("NotTilde")]; char entity_pool_str2177[sizeof("doublebarwedge")]; char entity_pool_str2179[sizeof("gap")]; char entity_pool_str2186[sizeof("bbrktbrk")]; char entity_pool_str2189[sizeof("swarrow")]; char entity_pool_str2190[sizeof("bepsi")]; char entity_pool_str2194[sizeof("Iscr")]; char entity_pool_str2198[sizeof("NotTildeFullEqual")]; char entity_pool_str2199[sizeof("eqcolon")]; char entity_pool_str2202[sizeof("tint")]; char entity_pool_str2205[sizeof("intprod")]; char entity_pool_str2207[sizeof("nsupE")]; char entity_pool_str2210[sizeof("nwarrow")]; char entity_pool_str2211[sizeof("nsubE")]; char entity_pool_str2214[sizeof("nges")]; char entity_pool_str2216[sizeof("Uparrow")]; char entity_pool_str2217[sizeof("ge")]; char entity_pool_str2218[sizeof("OpenCurlyDoubleQuote")]; char entity_pool_str2223[sizeof("smallsetminus")]; char entity_pool_str2228[sizeof("Scaron")]; char entity_pool_str2230[sizeof("nvltrie")]; char entity_pool_str2231[sizeof("ges")]; char entity_pool_str2232[sizeof("blank")]; char entity_pool_str2233[sizeof("QUOT")]; char entity_pool_str2238[sizeof("block")]; char entity_pool_str2239[sizeof("trade")]; char entity_pool_str2245[sizeof("jscr")]; char entity_pool_str2246[sizeof("wedge")]; char entity_pool_str2254[sizeof("Amacr")]; char entity_pool_str2256[sizeof("Equal")]; char entity_pool_str2259[sizeof("Dcaron")]; char entity_pool_str2262[sizeof("DotDot")]; char entity_pool_str2270[sizeof("gneq")]; char entity_pool_str2271[sizeof("varpropto")]; char entity_pool_str2273[sizeof("gneqq")]; char entity_pool_str2274[sizeof("Proportional")]; char entity_pool_str2279[sizeof("isins")]; char entity_pool_str2281[sizeof("eDDot")]; char entity_pool_str2282[sizeof("isin")]; char entity_pool_str2286[sizeof("TripleDot")]; char entity_pool_str2290[sizeof("Fouriertrf")]; char entity_pool_str2291[sizeof("Proportion")]; char entity_pool_str2294[sizeof("ngeq")]; char entity_pool_str2295[sizeof("Lcaron")]; char entity_pool_str2297[sizeof("ngeqq")]; char entity_pool_str2313[sizeof("lE")]; char entity_pool_str2314[sizeof("Ccaron")]; char entity_pool_str2320[sizeof("bsemi")]; char entity_pool_str2326[sizeof("propto")]; char entity_pool_str2331[sizeof("lesdot")]; char entity_pool_str2332[sizeof("Conint")]; char entity_pool_str2334[sizeof("And")]; char entity_pool_str2338[sizeof("searrow")]; char entity_pool_str2343[sizeof("orslope")]; char entity_pool_str2344[sizeof("harr")]; char entity_pool_str2350[sizeof("late")]; char entity_pool_str2352[sizeof("CenterDot")]; char entity_pool_str2355[sizeof("ofr")]; char entity_pool_str2359[sizeof("nearrow")]; char entity_pool_str2361[sizeof("qint")]; char entity_pool_str2364[sizeof("lates")]; char entity_pool_str2365[sizeof("kappav")]; char entity_pool_str2368[sizeof("horbar")]; char entity_pool_str2369[sizeof("Efr")]; char entity_pool_str2370[sizeof("hoarr")]; char entity_pool_str2371[sizeof("npre")]; char entity_pool_str2377[sizeof("inodot")]; char entity_pool_str2379[sizeof("udarr")]; char entity_pool_str2386[sizeof("geq")]; char entity_pool_str2391[sizeof("nsimeq")]; char entity_pool_str2404[sizeof("geqq")]; char entity_pool_str2407[sizeof("efDot")]; char entity_pool_str2410[sizeof("rpargt")]; char entity_pool_str2419[sizeof("Oscr")]; char entity_pool_str2422[sizeof("plusdo")]; char entity_pool_str2425[sizeof("lagran")]; char entity_pool_str2429[sizeof("thicksim")]; char entity_pool_str2440[sizeof("precnsim")]; char entity_pool_str2444[sizeof("Ncaron")]; char entity_pool_str2449[sizeof("napE")]; char entity_pool_str2457[sizeof("iiint")]; char entity_pool_str2470[sizeof("Bscr")]; char entity_pool_str2483[sizeof("mapstodown")]; char entity_pool_str2486[sizeof("varrho")]; char entity_pool_str2488[sizeof("isinsv")]; char entity_pool_str2491[sizeof("nvHarr")]; char entity_pool_str2494[sizeof("NotLeftTriangleBar")]; char entity_pool_str2496[sizeof("equest")]; char entity_pool_str2498[sizeof("NotLeftTriangleEqual")]; char entity_pool_str2499[sizeof("NotLeftTriangle")]; char entity_pool_str2502[sizeof("Aopf")]; char entity_pool_str2503[sizeof("hbar")]; char entity_pool_str2507[sizeof("vangrt")]; char entity_pool_str2511[sizeof("Hfr")]; char entity_pool_str2517[sizeof("range")]; char entity_pool_str2518[sizeof("smte")]; char entity_pool_str2519[sizeof("lsim")]; char entity_pool_str2521[sizeof("npolint")]; char entity_pool_str2523[sizeof("dcaron")]; char entity_pool_str2525[sizeof("esim")]; char entity_pool_str2527[sizeof("Union")]; char entity_pool_str2532[sizeof("smtes")]; char entity_pool_str2536[sizeof("kopf")]; char entity_pool_str2537[sizeof("gopf")]; char entity_pool_str2542[sizeof("nsim")]; char entity_pool_str2544[sizeof("bsim")]; char entity_pool_str2546[sizeof("SmallCircle")]; char entity_pool_str2548[sizeof("NotDoubleVerticalBar")]; char entity_pool_str2549[sizeof("NotNestedGreaterGreater")]; char entity_pool_str2565[sizeof("EqualTilde")]; char entity_pool_str2568[sizeof("notindot")]; char entity_pool_str2572[sizeof("Rcaron")]; char entity_pool_str2577[sizeof("Popf")]; char entity_pool_str2583[sizeof("Gopf")]; char entity_pool_str2586[sizeof("Ifr")]; char entity_pool_str2589[sizeof("wedgeq")]; char entity_pool_str2595[sizeof("prod")]; char entity_pool_str2617[sizeof("osol")]; char entity_pool_str2624[sizeof("DoubleUpArrow")]; char entity_pool_str2627[sizeof("Congruent")]; char entity_pool_str2631[sizeof("gnsim")]; char entity_pool_str2635[sizeof("scsim")]; char entity_pool_str2637[sizeof("jfr")]; char entity_pool_str2645[sizeof("upsih")]; char entity_pool_str2650[sizeof("nLl")]; char entity_pool_str2653[sizeof("DoubleUpDownArrow")]; char entity_pool_str2655[sizeof("ngsim")]; char entity_pool_str2664[sizeof("hearts")]; char entity_pool_str2666[sizeof("lesseqgtr")]; char entity_pool_str2670[sizeof("nesear")]; char entity_pool_str2676[sizeof("Exists")]; char entity_pool_str2687[sizeof("smile")]; char entity_pool_str2689[sizeof("uwangle")]; char entity_pool_str2693[sizeof("heartsuit")]; char entity_pool_str2700[sizeof("HorizontalLine")]; char entity_pool_str2703[sizeof("GreaterLess")]; char entity_pool_str2705[sizeof("rsaquo")]; char entity_pool_str2707[sizeof("lsaquo")]; char entity_pool_str2709[sizeof("realine")]; char entity_pool_str2710[sizeof("Dashv")]; char entity_pool_str2714[sizeof("simdot")]; char entity_pool_str2715[sizeof("GreaterEqual")]; char entity_pool_str2716[sizeof("GreaterTilde")]; char entity_pool_str2721[sizeof("GreaterEqualLess")]; char entity_pool_str2723[sizeof("GreaterGreater")]; char entity_pool_str2737[sizeof("rceil")]; char entity_pool_str2739[sizeof("lceil")]; char entity_pool_str2743[sizeof("lessgtr")]; char entity_pool_str2746[sizeof("oline")]; char entity_pool_str2753[sizeof("thksim")]; char entity_pool_str2755[sizeof("InvisibleTimes")]; char entity_pool_str2762[sizeof("race")]; char entity_pool_str2766[sizeof("iquest")]; char entity_pool_str2774[sizeof("imagline")]; char entity_pool_str2779[sizeof("UpTee")]; char entity_pool_str2781[sizeof("midcir")]; char entity_pool_str2790[sizeof("ofcir")]; char entity_pool_str2793[sizeof("ddarr")]; char entity_pool_str2800[sizeof("rangd")]; char entity_pool_str2802[sizeof("langd")]; char entity_pool_str2808[sizeof("Equilibrium")]; char entity_pool_str2809[sizeof("parsim")]; char entity_pool_str2810[sizeof("Vdashl")]; char entity_pool_str2811[sizeof("Ofr")]; char entity_pool_str2816[sizeof("Because")]; char entity_pool_str2818[sizeof("rAtail")]; char entity_pool_str2820[sizeof("lAtail")]; char entity_pool_str2821[sizeof("ominus")]; char entity_pool_str2822[sizeof("Ascr")]; char entity_pool_str2826[sizeof("Epsilon")]; char entity_pool_str2832[sizeof("ShortLeftArrow")]; char entity_pool_str2845[sizeof("isinv")]; char entity_pool_str2847[sizeof("micro")]; char entity_pool_str2851[sizeof("zcaron")]; char entity_pool_str2856[sizeof("kscr")]; char entity_pool_str2857[sizeof("gscr")]; char entity_pool_str2862[sizeof("Bfr")]; char entity_pool_str2863[sizeof("gel")]; char entity_pool_str2864[sizeof("hercon")]; char entity_pool_str2871[sizeof("triminus")]; char entity_pool_str2877[sizeof("egrave")]; char entity_pool_str2881[sizeof("sdot")]; char entity_pool_str2882[sizeof("ugrave")]; char entity_pool_str2884[sizeof("Zdot")]; char entity_pool_str2885[sizeof("edot")]; char entity_pool_str2890[sizeof("NotTildeTilde")]; char entity_pool_str2892[sizeof("tdot")]; char entity_pool_str2897[sizeof("Pscr")]; char entity_pool_str2898[sizeof("Pi")]; char entity_pool_str2903[sizeof("Gscr")]; char entity_pool_str2910[sizeof("plustwo")]; char entity_pool_str2914[sizeof("NotElement")]; char entity_pool_str2916[sizeof("PlusMinus")]; char entity_pool_str2919[sizeof("hopf")]; char entity_pool_str2920[sizeof("gammad")]; char entity_pool_str2922[sizeof("mDDot")]; char entity_pool_str2926[sizeof("divideontimes")]; char entity_pool_str2940[sizeof("doteq")]; char entity_pool_str2956[sizeof("varepsilon")]; char entity_pool_str2963[sizeof("Precedes")]; char entity_pool_str2966[sizeof("Gammad")]; char entity_pool_str2974[sizeof("dashv")]; char entity_pool_str2979[sizeof("NotCongruent")]; char entity_pool_str2982[sizeof("ubreve")]; char entity_pool_str2990[sizeof("ogt")]; char entity_pool_str2994[sizeof("RoundImplies")]; char entity_pool_str3002[sizeof("PrecedesSlantEqual")]; char entity_pool_str3005[sizeof("sime")]; char entity_pool_str3014[sizeof("Ugrave")]; char entity_pool_str3016[sizeof("dbkarow")]; char entity_pool_str3021[sizeof("sdote")]; char entity_pool_str3023[sizeof("veeeq")]; char entity_pool_str3027[sizeof("mapsto")]; char entity_pool_str3030[sizeof("times")]; char entity_pool_str3033[sizeof("rangle")]; char entity_pool_str3035[sizeof("langle")]; char entity_pool_str3038[sizeof("leftarrowtail")]; char entity_pool_str3039[sizeof("hamilt")]; char entity_pool_str3044[sizeof("udhar")]; char entity_pool_str3053[sizeof("nisd")]; char entity_pool_str3055[sizeof("rfisht")]; char entity_pool_str3057[sizeof("lfisht")]; char entity_pool_str3058[sizeof("harrcir")]; char entity_pool_str3066[sizeof("OpenCurlyQuote")]; char entity_pool_str3068[sizeof("ufisht")]; char entity_pool_str3069[sizeof("NotHumpDownHump")]; char entity_pool_str3072[sizeof("LeftTee")]; char entity_pool_str3074[sizeof("rsh")]; char entity_pool_str3076[sizeof("lsh")]; char entity_pool_str3080[sizeof("gvertneqq")]; char entity_pool_str3083[sizeof("timesb")]; char entity_pool_str3092[sizeof("scpolint")]; char entity_pool_str3095[sizeof("Cdot")]; char entity_pool_str3103[sizeof("dwangle")]; char entity_pool_str3114[sizeof("Ubreve")]; char entity_pool_str3132[sizeof("LeftUpVector")]; char entity_pool_str3135[sizeof("LeftUpVectorBar")]; char entity_pool_str3139[sizeof("Ecaron")]; char entity_pool_str3142[sizeof("homtht")]; char entity_pool_str3147[sizeof("igrave")]; char entity_pool_str3155[sizeof("npreceq")]; char entity_pool_str3156[sizeof("ecolon")]; char entity_pool_str3167[sizeof("dd")]; char entity_pool_str3174[sizeof("simeq")]; char entity_pool_str3179[sizeof("notinE")]; char entity_pool_str3198[sizeof("bigoplus")]; char entity_pool_str3214[sizeof("Afr")]; char entity_pool_str3215[sizeof("leftarrow")]; char entity_pool_str3216[sizeof("oint")]; char entity_pool_str3218[sizeof("Tab")]; char entity_pool_str3227[sizeof("ogon")]; char entity_pool_str3230[sizeof("lt")]; char entity_pool_str3231[sizeof("nLeftrightarrow")]; char entity_pool_str3235[sizeof("rarrb")]; char entity_pool_str3237[sizeof("larrb")]; char entity_pool_str3239[sizeof("hscr")]; char entity_pool_str3246[sizeof("LeftUpDownVector")]; char entity_pool_str3248[sizeof("kfr")]; char entity_pool_str3249[sizeof("gfr")]; char entity_pool_str3250[sizeof("UpArrowBar")]; char entity_pool_str3259[sizeof("nsce")]; char entity_pool_str3260[sizeof("ltdot")]; char entity_pool_str3261[sizeof("gesl")]; char entity_pool_str3262[sizeof("xodot")]; char entity_pool_str3263[sizeof("star")]; char entity_pool_str3266[sizeof("lowbar")]; char entity_pool_str3268[sizeof("xharr")]; char entity_pool_str3269[sizeof("ecir")]; char entity_pool_str3271[sizeof("utdot")]; char entity_pool_str3272[sizeof("natur")]; char entity_pool_str3273[sizeof("Lsh")]; char entity_pool_str3274[sizeof("infin")]; char entity_pool_str3276[sizeof("comp")]; char entity_pool_str3278[sizeof("sigmav")]; char entity_pool_str3285[sizeof("xotime")]; char entity_pool_str3289[sizeof("Pfr")]; char entity_pool_str3295[sizeof("Gfr")]; char entity_pool_str3298[sizeof("bigcap")]; char entity_pool_str3300[sizeof("simlE")]; char entity_pool_str3319[sizeof("iiiint")]; char entity_pool_str3320[sizeof("barwedge")]; char entity_pool_str3321[sizeof("Barwed")]; char entity_pool_str3329[sizeof("xlarr")]; char entity_pool_str3330[sizeof("LessEqualGreater")]; char entity_pool_str3332[sizeof("crarr")]; char entity_pool_str3333[sizeof("isindot")]; char entity_pool_str3335[sizeof("commat")]; char entity_pool_str3342[sizeof("middot")]; char entity_pool_str3349[sizeof("lesdotor")]; char entity_pool_str3356[sizeof("sigmaf")]; char entity_pool_str3366[sizeof("rarrbfs")]; char entity_pool_str3368[sizeof("larrbfs")]; char entity_pool_str3371[sizeof("xrarr")]; char entity_pool_str3376[sizeof("bigcup")]; char entity_pool_str3378[sizeof("clubs")]; char entity_pool_str3379[sizeof("hArr")]; char entity_pool_str3380[sizeof("rtrie")]; char entity_pool_str3382[sizeof("ltrie")]; char entity_pool_str3383[sizeof("imped")]; char entity_pool_str3388[sizeof("eogon")]; char entity_pool_str3389[sizeof("rx")]; char entity_pool_str3390[sizeof("ltrPar")]; char entity_pool_str3391[sizeof("Star")]; char entity_pool_str3393[sizeof("uogon")]; char entity_pool_str3396[sizeof("Tilde")]; char entity_pool_str3398[sizeof("half")]; char entity_pool_str3405[sizeof("tilde")]; char entity_pool_str3412[sizeof("Leftarrow")]; char entity_pool_str3417[sizeof("gesles")]; char entity_pool_str3422[sizeof("cap")]; char entity_pool_str3423[sizeof("strns")]; char entity_pool_str3427[sizeof("Lt")]; char entity_pool_str3439[sizeof("prnE")]; char entity_pool_str3447[sizeof("sqsupe")]; char entity_pool_str3462[sizeof("sqsupset")]; char entity_pool_str3467[sizeof("tridot")]; char entity_pool_str3468[sizeof("order")]; char entity_pool_str3471[sizeof("caps")]; char entity_pool_str3475[sizeof("cross")]; char entity_pool_str3482[sizeof("dfisht")]; char entity_pool_str3487[sizeof("xmap")]; char entity_pool_str3491[sizeof("sqsup")]; char entity_pool_str3503[sizeof("rtri")]; char entity_pool_str3505[sizeof("ltri")]; char entity_pool_str3506[sizeof("it")]; char entity_pool_str3507[sizeof("rmoust")]; char entity_pool_str3509[sizeof("lmoust")]; char entity_pool_str3510[sizeof("gnE")]; char entity_pool_str3511[sizeof("lgE")]; char entity_pool_str3514[sizeof("scE")]; char entity_pool_str3516[sizeof("utri")]; char entity_pool_str3518[sizeof("vellip")]; char entity_pool_str3520[sizeof("ETH")]; char entity_pool_str3523[sizeof("lmidot")]; char entity_pool_str3525[sizeof("Uogon")]; char entity_pool_str3526[sizeof("CounterClockwiseContourIntegral")]; char entity_pool_str3534[sizeof("ngE")]; char entity_pool_str3535[sizeof("nwnear")]; char entity_pool_str3543[sizeof("lesg")]; char entity_pool_str3546[sizeof("plusb")]; char entity_pool_str3550[sizeof("Rsh")]; char entity_pool_str3555[sizeof("copysr")]; char entity_pool_str3557[sizeof("infintie")]; char entity_pool_str3559[sizeof("imath")]; char entity_pool_str3560[sizeof("Esim")]; char entity_pool_str3565[sizeof("Phi")]; char entity_pool_str3573[sizeof("glE")]; char entity_pool_str3579[sizeof("vnsup")]; char entity_pool_str3582[sizeof("simgE")]; char entity_pool_str3586[sizeof("DoubleLongLeftArrow")]; char entity_pool_str3591[sizeof("DoubleLongLeftRightArrow")]; char entity_pool_str3594[sizeof("nvgt")]; char entity_pool_str3607[sizeof("Mellintrf")]; char entity_pool_str3611[sizeof("Prime")]; char entity_pool_str3615[sizeof("iinfin")]; char entity_pool_str3620[sizeof("ReverseElement")]; char entity_pool_str3627[sizeof("EmptySmallSquare")]; char entity_pool_str3628[sizeof("radic")]; char entity_pool_str3631[sizeof("hfr")]; char entity_pool_str3632[sizeof("zdot")]; char entity_pool_str3633[sizeof("male")]; char entity_pool_str3635[sizeof("rarrc")]; char entity_pool_str3636[sizeof("prec")]; char entity_pool_str3637[sizeof("scnap")]; char entity_pool_str3641[sizeof("DifferentialD")]; char entity_pool_str3643[sizeof("models")]; char entity_pool_str3657[sizeof("ltcir")]; char entity_pool_str3658[sizeof("iogon")]; char entity_pool_str3665[sizeof("capcap")]; char entity_pool_str3667[sizeof("iff")]; char entity_pool_str3669[sizeof("ddotseq")]; char entity_pool_str3671[sizeof("CirclePlus")]; char entity_pool_str3676[sizeof("rthree")]; char entity_pool_str3678[sizeof("lthree")]; char entity_pool_str3681[sizeof("PrecedesTilde")]; char entity_pool_str3685[sizeof("dtdot")]; char entity_pool_str3687[sizeof("clubsuit")]; char entity_pool_str3689[sizeof("racute")]; char entity_pool_str3691[sizeof("lacute")]; char entity_pool_str3692[sizeof("trpezium")]; char entity_pool_str3693[sizeof("sacute")]; char entity_pool_str3696[sizeof("Zacute")]; char entity_pool_str3697[sizeof("eacute")]; char entity_pool_str3699[sizeof("TildeTilde")]; char entity_pool_str3701[sizeof("Uarrocir")]; char entity_pool_str3702[sizeof("uacute")]; char entity_pool_str3703[sizeof("lowast")]; char entity_pool_str3714[sizeof("nacute")]; char entity_pool_str3716[sizeof("NotPrecedes")]; char entity_pool_str3720[sizeof("Lmidot")]; char entity_pool_str3725[sizeof("UpArrow")]; char entity_pool_str3727[sizeof("rarrw")]; char entity_pool_str3738[sizeof("DownTee")]; char entity_pool_str3742[sizeof("FilledSmallSquare")]; char entity_pool_str3743[sizeof("capcup")]; char entity_pool_str3749[sizeof("GreaterFullEqual")]; char entity_pool_str3756[sizeof("nvle")]; char entity_pool_str3758[sizeof("trie")]; char entity_pool_str3764[sizeof("omicron")]; char entity_pool_str3766[sizeof("DoubleRightTee")]; char entity_pool_str3767[sizeof("Cconint")]; char entity_pool_str3768[sizeof("rsquor")]; char entity_pool_str3770[sizeof("lsquor")]; char entity_pool_str3772[sizeof("zigrarr")]; char entity_pool_str3780[sizeof("copf")]; char entity_pool_str3782[sizeof("ContourIntegral")]; char entity_pool_str3798[sizeof("hairsp")]; char entity_pool_str3799[sizeof("sqsupseteq")]; char entity_pool_str3800[sizeof("csub")]; char entity_pool_str3801[sizeof("upharpoonright")]; char entity_pool_str3805[sizeof("DownBreve")]; char entity_pool_str3817[sizeof("ShortDownArrow")]; char entity_pool_str3819[sizeof("xopf")]; char entity_pool_str3821[sizeof("Sacute")]; char entity_pool_str3829[sizeof("vsupnE")]; char entity_pool_str3830[sizeof("cir")]; char entity_pool_str3831[sizeof("plusacir")]; char entity_pool_str3832[sizeof("csup")]; char entity_pool_str3833[sizeof("vsubnE")]; char entity_pool_str3834[sizeof("Uacute")]; char entity_pool_str3836[sizeof("isinE")]; char entity_pool_str3845[sizeof("gEl")]; char entity_pool_str3851[sizeof("sqcups")]; char entity_pool_str3853[sizeof("smid")]; char entity_pool_str3855[sizeof("lg")]; char entity_pool_str3857[sizeof("DoubleLongRightArrow")]; char entity_pool_str3858[sizeof("NotPrecedesSlantEqual")]; char entity_pool_str3861[sizeof("eg")]; char entity_pool_str3864[sizeof("AMP")]; char entity_pool_str3874[sizeof("nmid")]; char entity_pool_str3883[sizeof("timesd")]; char entity_pool_str3886[sizeof("DownLeftVector")]; char entity_pool_str3887[sizeof("zwnj")]; char entity_pool_str3888[sizeof("Lacute")]; char entity_pool_str3889[sizeof("DownLeftVectorBar")]; char entity_pool_str3898[sizeof("ograve")]; char entity_pool_str3899[sizeof("Yacute")]; char entity_pool_str3903[sizeof("sqcup")]; char entity_pool_str3906[sizeof("odot")]; char entity_pool_str3907[sizeof("Cacute")]; char entity_pool_str3909[sizeof("nu")]; char entity_pool_str3910[sizeof("tritime")]; char entity_pool_str3912[sizeof("Egrave")]; char entity_pool_str3913[sizeof("eplus")]; char entity_pool_str3915[sizeof("backcong")]; char entity_pool_str3918[sizeof("uplus")]; char entity_pool_str3920[sizeof("Edot")]; char entity_pool_str3924[sizeof("csupe")]; char entity_pool_str3926[sizeof("simg")]; char entity_pool_str3927[sizeof("UpperRightArrow")]; char entity_pool_str3928[sizeof("csube")]; char entity_pool_str3930[sizeof("dtri")]; char entity_pool_str3931[sizeof("prnsim")]; char entity_pool_str3936[sizeof("boxUr")]; char entity_pool_str3937[sizeof("uuarr")]; char entity_pool_str3945[sizeof("DownLeftTeeVector")]; char entity_pool_str3946[sizeof("gsime")]; char entity_pool_str3950[sizeof("bigotimes")]; char entity_pool_str3951[sizeof("Dagger")]; char entity_pool_str3954[sizeof("Intersection")]; char entity_pool_str3967[sizeof("iacute")]; char entity_pool_str3969[sizeof("prcue")]; char entity_pool_str3981[sizeof("egsdot")]; char entity_pool_str3987[sizeof("Implies")]; char entity_pool_str3988[sizeof("VDash")]; char entity_pool_str3996[sizeof("bump")]; char entity_pool_str4015[sizeof("Mu")]; char entity_pool_str4022[sizeof("vDash")]; char entity_pool_str4028[sizeof("lvnE")]; char entity_pool_str4033[sizeof("LeftTeeArrow")]; char entity_pool_str4037[sizeof("Nacute")]; char entity_pool_str4042[sizeof("UnderBrace")]; char entity_pool_str4043[sizeof("Psi")]; char entity_pool_str4047[sizeof("rhov")]; char entity_pool_str4049[sizeof("lescc")]; char entity_pool_str4055[sizeof("sup1")]; char entity_pool_str4058[sizeof("sup2")]; char entity_pool_str4066[sizeof("sup3")]; char entity_pool_str4071[sizeof("bigodot")]; char entity_pool_str4078[sizeof("Downarrow")]; char entity_pool_str4080[sizeof("xsqcup")]; char entity_pool_str4082[sizeof("barvee")]; char entity_pool_str4087[sizeof("NegativeMediumSpace")]; char entity_pool_str4088[sizeof("bumpe")]; char entity_pool_str4100[sizeof("cscr")]; char entity_pool_str4109[sizeof("nsc")]; char entity_pool_str4115[sizeof("sup")]; char entity_pool_str4122[sizeof("cedil")]; char entity_pool_str4125[sizeof("boxVr")]; char entity_pool_str4127[sizeof("origof")]; char entity_pool_str4128[sizeof("zwj")]; char entity_pool_str4129[sizeof("Igrave")]; char entity_pool_str4137[sizeof("Idot")]; char entity_pool_str4139[sizeof("xscr")]; char entity_pool_str4140[sizeof("xi")]; char entity_pool_str4144[sizeof("nGtv")]; char entity_pool_str4153[sizeof("boxHu")]; char entity_pool_str4163[sizeof("THORN")]; char entity_pool_str4165[sizeof("Racute")]; char entity_pool_str4167[sizeof("rarrhk")]; char entity_pool_str4169[sizeof("larrhk")]; char entity_pool_str4177[sizeof("rtriltri")]; char entity_pool_str4189[sizeof("boxV")]; char entity_pool_str4215[sizeof("dagger")]; char entity_pool_str4220[sizeof("Omicron")]; char entity_pool_str4226[sizeof("DoubleVerticalBar")]; char entity_pool_str4229[sizeof("nexists")]; char entity_pool_str4232[sizeof("Nu")]; char entity_pool_str4233[sizeof("nexist")]; char entity_pool_str4234[sizeof("gE")]; char entity_pool_str4238[sizeof("ap")]; char entity_pool_str4243[sizeof("Sup")]; char entity_pool_str4244[sizeof("doteqdot")]; char entity_pool_str4247[sizeof("eng")]; char entity_pool_str4249[sizeof("caron")]; char entity_pool_str4251[sizeof("boxHU")]; char entity_pool_str4252[sizeof("gesdot")]; char entity_pool_str4257[sizeof("ReverseEquilibrium")]; char entity_pool_str4262[sizeof("boxUL")]; char entity_pool_str4264[sizeof("supmult")]; char entity_pool_str4267[sizeof("pitchfork")]; char entity_pool_str4272[sizeof("numsp")]; char entity_pool_str4285[sizeof("rang")]; char entity_pool_str4287[sizeof("lang")]; char entity_pool_str4290[sizeof("ocir")]; char entity_pool_str4292[sizeof("rationals")]; char entity_pool_str4294[sizeof("coprod")]; char entity_pool_str4307[sizeof("ltlarr")]; char entity_pool_str4308[sizeof("breve")]; char entity_pool_str4310[sizeof("nang")]; char entity_pool_str4315[sizeof("swarhk")]; char entity_pool_str4322[sizeof("raquo")]; char entity_pool_str4324[sizeof("laquo")]; char entity_pool_str4325[sizeof("supsub")]; char entity_pool_str4329[sizeof("Cup")]; char entity_pool_str4330[sizeof("ape")]; char entity_pool_str4331[sizeof("quest")]; char entity_pool_str4336[sizeof("nwarhk")]; char entity_pool_str4340[sizeof("supset")]; char entity_pool_str4342[sizeof("downarrow")]; char entity_pool_str4351[sizeof("duarr")]; char entity_pool_str4353[sizeof("apos")]; char entity_pool_str4354[sizeof("Ograve")]; char entity_pool_str4355[sizeof("shortparallel")]; char entity_pool_str4364[sizeof("nsucc")]; char entity_pool_str4368[sizeof("LongLeftArrow")]; char entity_pool_str4377[sizeof("lesdoto")]; char entity_pool_str4384[sizeof("supne")]; char entity_pool_str4388[sizeof("nGg")]; char entity_pool_str4396[sizeof("raemptyv")]; char entity_pool_str4397[sizeof("supsup")]; char entity_pool_str4398[sizeof("laemptyv")]; char entity_pool_str4401[sizeof("topfork")]; char entity_pool_str4423[sizeof("Eogon")]; char entity_pool_str4429[sizeof("risingdotseq")]; char entity_pool_str4431[sizeof("bumpeq")]; char entity_pool_str4435[sizeof("lstrok")]; char entity_pool_str4439[sizeof("Tstrok")]; char entity_pool_str4440[sizeof("gsim")]; char entity_pool_str4443[sizeof("bemptyv")]; char entity_pool_str4444[sizeof("zacute")]; char entity_pool_str4445[sizeof("gsiml")]; char entity_pool_str4448[sizeof("tstrok")]; char entity_pool_str4450[sizeof("roang")]; char entity_pool_str4451[sizeof("boxVL")]; char entity_pool_str4452[sizeof("loang")]; char entity_pool_str4456[sizeof("nleqslant")]; char entity_pool_str4462[sizeof("sbquo")]; char entity_pool_str4464[sizeof("searhk")]; char entity_pool_str4465[sizeof("lnapprox")]; char entity_pool_str4468[sizeof("Supset")]; char entity_pool_str4470[sizeof("boxHd")]; char entity_pool_str4471[sizeof("varkappa")]; char entity_pool_str4475[sizeof("circeq")]; char entity_pool_str4477[sizeof("yopf")]; char entity_pool_str4479[sizeof("UnionPlus")]; char entity_pool_str4484[sizeof("Lang")]; char entity_pool_str4485[sizeof("nearhk")]; char entity_pool_str4486[sizeof("shcy")]; char entity_pool_str4492[sizeof("cfr")]; char entity_pool_str4506[sizeof("Kappa")]; char entity_pool_str4507[sizeof("ljcy")]; char entity_pool_str4508[sizeof("MediumSpace")]; char entity_pool_str4511[sizeof("supseteq")]; char entity_pool_str4512[sizeof("supseteqq")]; char entity_pool_str4517[sizeof("reg")]; char entity_pool_str4518[sizeof("amacr")]; char entity_pool_str4519[sizeof("leg")]; char entity_pool_str4524[sizeof("weierp")]; char entity_pool_str4525[sizeof("TScy")]; char entity_pool_str4529[sizeof("supsetneq")]; char entity_pool_str4530[sizeof("njcy")]; char entity_pool_str4531[sizeof("xfr")]; char entity_pool_str4533[sizeof("mu")]; char entity_pool_str4539[sizeof("nvinfin")]; char entity_pool_str4540[sizeof("boxUR")]; char entity_pool_str4545[sizeof("xoplus")]; char entity_pool_str4551[sizeof("leftleftarrows")]; char entity_pool_str4552[sizeof("sum")]; char entity_pool_str4559[sizeof("beth")]; char entity_pool_str4563[sizeof("complement")]; char entity_pool_str4573[sizeof("num")]; char entity_pool_str4574[sizeof("amp")]; char entity_pool_str4583[sizeof("boxUl")]; char entity_pool_str4590[sizeof("NotGreater")]; char entity_pool_str4591[sizeof("boxplus")]; char entity_pool_str4592[sizeof("jmath")]; char entity_pool_str4594[sizeof("sfrown")]; char entity_pool_str4596[sizeof("Dstrok")]; char entity_pool_str4598[sizeof("and")]; char entity_pool_str4599[sizeof("NotGreaterGreater")]; char entity_pool_str4606[sizeof("NotGreaterSlantEqual")]; char entity_pool_str4608[sizeof("NotGreaterLess")]; char entity_pool_str4609[sizeof("quot")]; char entity_pool_str4616[sizeof("NotGreaterFullEqual")]; char entity_pool_str4617[sizeof("hyphen")]; char entity_pool_str4618[sizeof("planck")]; char entity_pool_str4620[sizeof("TildeEqual")]; char entity_pool_str4627[sizeof("tosa")]; char entity_pool_str4632[sizeof("Lstrok")]; char entity_pool_str4635[sizeof("shy")]; char entity_pool_str4639[sizeof("xnis")]; char entity_pool_str4640[sizeof("Iogon")]; char entity_pool_str4643[sizeof("DZcy")]; char entity_pool_str4645[sizeof("ohbar")]; char entity_pool_str4652[sizeof("cirscir")]; char entity_pool_str4654[sizeof("sext")]; char entity_pool_str4668[sizeof("para")]; char entity_pool_str4671[sizeof("ast")]; char entity_pool_str4678[sizeof("questeq")]; char entity_pool_str4680[sizeof("Sum")]; char entity_pool_str4682[sizeof("DScy")]; char entity_pool_str4684[sizeof("ENG")]; char entity_pool_str4686[sizeof("ZHcy")]; char entity_pool_str4689[sizeof("longleftarrow")]; char entity_pool_str4691[sizeof("dash")]; char entity_pool_str4699[sizeof("DownTeeArrow")]; char entity_pool_str4706[sizeof("supsetneqq")]; char entity_pool_str4714[sizeof("profalar")]; char entity_pool_str4718[sizeof("oacute")]; char entity_pool_str4729[sizeof("boxVR")]; char entity_pool_str4732[sizeof("Eacute")]; char entity_pool_str4738[sizeof("supplus")]; char entity_pool_str4740[sizeof("hookleftarrow")]; char entity_pool_str4743[sizeof("CloseCurlyQuote")]; char entity_pool_str4746[sizeof("trisb")]; char entity_pool_str4747[sizeof("dotsquare")]; char entity_pool_str4751[sizeof("rtimes")]; char entity_pool_str4753[sizeof("ltimes")]; char entity_pool_str4756[sizeof("toea")]; char entity_pool_str4757[sizeof("Agrave")]; char entity_pool_str4760[sizeof("Assign")]; char entity_pool_str4761[sizeof("Rang")]; char entity_pool_str4762[sizeof("iocy")]; char entity_pool_str4764[sizeof("NotPrecedesEqual")]; char entity_pool_str4766[sizeof("aopf")]; char entity_pool_str4768[sizeof("chi")]; char entity_pool_str4771[sizeof("quaternions")]; char entity_pool_str4772[sizeof("boxVl")]; char entity_pool_str4773[sizeof("NotGreaterEqual")]; char entity_pool_str4777[sizeof("xhArr")]; char entity_pool_str4791[sizeof("orderof")]; char entity_pool_str4794[sizeof("rsquo")]; char entity_pool_str4796[sizeof("lsquo")]; char entity_pool_str4797[sizeof("yscr")]; char entity_pool_str4800[sizeof("gdot")]; char entity_pool_str4802[sizeof("NotSquareSubsetEqual")]; char entity_pool_str4803[sizeof("KHcy")]; char entity_pool_str4809[sizeof("bsolb")]; char entity_pool_str4810[sizeof("NotSquareSubset")]; char entity_pool_str4811[sizeof("SHcy")]; char entity_pool_str4821[sizeof("YIcy")]; char entity_pool_str4825[sizeof("cwint")]; char entity_pool_str4828[sizeof("Theta")]; char entity_pool_str4837[sizeof("theta")]; char entity_pool_str4838[sizeof("xlArr")]; char entity_pool_str4840[sizeof("NotSquareSupersetEqual")]; char entity_pool_str4843[sizeof("demptyv")]; char entity_pool_str4844[sizeof("triangle")]; char entity_pool_str4846[sizeof("Gdot")]; char entity_pool_str4848[sizeof("NotSquareSuperset")]; char entity_pool_str4857[sizeof("Abreve")]; char entity_pool_str4860[sizeof("dstrok")]; char entity_pool_str4861[sizeof("pertenk")]; char entity_pool_str4866[sizeof("rbrack")]; char entity_pool_str4868[sizeof("lbrack")]; char entity_pool_str4872[sizeof("odsold")]; char entity_pool_str4878[sizeof("omid")]; char entity_pool_str4880[sizeof("xrArr")]; char entity_pool_str4882[sizeof("triangleleft")]; char entity_pool_str4883[sizeof("NotGreaterTilde")]; char entity_pool_str4884[sizeof("colone")]; char entity_pool_str4886[sizeof("Longleftarrow")]; char entity_pool_str4888[sizeof("iota")]; char entity_pool_str4890[sizeof("colon")]; char entity_pool_str4891[sizeof("Zeta")]; char entity_pool_str4892[sizeof("gbreve")]; char entity_pool_str4897[sizeof("CHcy")]; char entity_pool_str4900[sizeof("YUcy")]; char entity_pool_str4901[sizeof("REG")]; char entity_pool_str4902[sizeof("szlig")]; char entity_pool_str4909[sizeof("dzcy")]; char entity_pool_str4911[sizeof("beta")]; char entity_pool_str4918[sizeof("euro")]; char entity_pool_str4921[sizeof("LeftArrow")]; char entity_pool_str4924[sizeof("CapitalDifferentialD")]; char entity_pool_str4926[sizeof("ring")]; char entity_pool_str4927[sizeof("Laplacetrf")]; char entity_pool_str4932[sizeof("djcy")]; char entity_pool_str4934[sizeof("oplus")]; char entity_pool_str4937[sizeof("integers")]; char entity_pool_str4938[sizeof("Gbreve")]; char entity_pool_str4940[sizeof("ubrcy")]; char entity_pool_str4941[sizeof("euml")]; char entity_pool_str4944[sizeof("deg")]; char entity_pool_str4946[sizeof("uuml")]; char entity_pool_str4949[sizeof("Iacute")]; char entity_pool_str4950[sizeof("succeq")]; char entity_pool_str4952[sizeof("KJcy")]; char entity_pool_str4961[sizeof("CupCap")]; char entity_pool_str4975[sizeof("tscy")]; char entity_pool_str4982[sizeof("cent")]; char entity_pool_str4991[sizeof("DJcy")]; char entity_pool_str5009[sizeof("TildeFullEqual")]; char entity_pool_str5011[sizeof("triangleq")]; char entity_pool_str5016[sizeof("duhar")]; char entity_pool_str5025[sizeof("LeftDoubleBracket")]; char entity_pool_str5027[sizeof("LJcy")]; char entity_pool_str5036[sizeof("iecy")]; char entity_pool_str5043[sizeof("trianglelefteq")]; char entity_pool_str5049[sizeof("nequiv")]; char entity_pool_str5055[sizeof("nshortparallel")]; char entity_pool_str5062[sizeof("ndash")]; char entity_pool_str5063[sizeof("bowtie")]; char entity_pool_str5065[sizeof("fjlig")]; char entity_pool_str5072[sizeof("Ubrcy")]; char entity_pool_str5074[sizeof("vartheta")]; char entity_pool_str5078[sizeof("Uuml")]; char entity_pool_str5084[sizeof("vartriangleright")]; char entity_pool_str5085[sizeof("vartriangleleft")]; char entity_pool_str5086[sizeof("ascr")]; char entity_pool_str5089[sizeof("succcurlyeq")]; char entity_pool_str5093[sizeof("cwconint")]; char entity_pool_str5101[sizeof("sc")]; char entity_pool_str5103[sizeof("fllig")]; char entity_pool_str5105[sizeof("circledast")]; char entity_pool_str5108[sizeof("Vdash")]; char entity_pool_str5112[sizeof("nVdash")]; char entity_pool_str5120[sizeof("suplarr")]; char entity_pool_str5124[sizeof("robrk")]; char entity_pool_str5126[sizeof("lobrk")]; char entity_pool_str5142[sizeof("vdash")]; char entity_pool_str5143[sizeof("Yuml")]; char entity_pool_str5151[sizeof("gt")]; char entity_pool_str5156[sizeof("ccaps")]; char entity_pool_str5173[sizeof("Succeeds")]; char entity_pool_str5174[sizeof("Oacute")]; char entity_pool_str5175[sizeof("TRADE")]; char entity_pool_str5176[sizeof("NJcy")]; char entity_pool_str5181[sizeof("gtdot")]; char entity_pool_str5189[sizeof("yfr")]; char entity_pool_str5192[sizeof("compfn")]; char entity_pool_str5197[sizeof("Gt")]; char entity_pool_str5198[sizeof("scnE")]; char entity_pool_str5199[sizeof("ijlig")]; char entity_pool_str5203[sizeof("circledS")]; char entity_pool_str5206[sizeof("yen")]; char entity_pool_str5208[sizeof("thetasym")]; char entity_pool_str5211[sizeof("iuml")]; char entity_pool_str5212[sizeof("SucceedsSlantEqual")]; char entity_pool_str5217[sizeof("boxH")]; char entity_pool_str5218[sizeof("mumap")]; char entity_pool_str5222[sizeof("rightrightarrows")]; char entity_pool_str5227[sizeof("coloneq")]; char entity_pool_str5229[sizeof("Sc")]; char entity_pool_str5230[sizeof("glj")]; char entity_pool_str5231[sizeof("iexcl")]; char entity_pool_str5234[sizeof("ccups")]; char entity_pool_str5236[sizeof("xcap")]; char entity_pool_str5237[sizeof("zhcy")]; char entity_pool_str5241[sizeof("boxHD")]; char entity_pool_str5250[sizeof("leqslant")]; char entity_pool_str5252[sizeof("UpperLeftArrow")]; char entity_pool_str5257[sizeof("dblac")]; char entity_pool_str5260[sizeof("puncsp")]; char entity_pool_str5262[sizeof("ccaron")]; char entity_pool_str5264[sizeof("rbbrk")]; char entity_pool_str5266[sizeof("lbbrk")]; char entity_pool_str5268[sizeof("Aogon")]; char entity_pool_str5269[sizeof("LeftTriangleBar")]; char entity_pool_str5272[sizeof("gesdotol")]; char entity_pool_str5273[sizeof("LeftTriangleEqual")]; char entity_pool_str5274[sizeof("LeftTriangle")]; char entity_pool_str5280[sizeof("conint")]; char entity_pool_str5283[sizeof("drbkarow")]; char entity_pool_str5295[sizeof("rtrif")]; char entity_pool_str5297[sizeof("ltrif")]; char entity_pool_str5300[sizeof("ReverseUpEquilibrium")]; char entity_pool_str5306[sizeof("LeftCeiling")]; char entity_pool_str5308[sizeof("utrif")]; char entity_pool_str5314[sizeof("xcup")]; char entity_pool_str5319[sizeof("fallingdotseq")]; char entity_pool_str5325[sizeof("rcedil")]; char entity_pool_str5327[sizeof("lcedil")]; char entity_pool_str5329[sizeof("scedil")]; char entity_pool_str5331[sizeof("Tcedil")]; char entity_pool_str5333[sizeof("starf")]; char entity_pool_str5334[sizeof("boxminus")]; char entity_pool_str5340[sizeof("tcedil")]; char entity_pool_str5341[sizeof("ZeroWidthSpace")]; char entity_pool_str5350[sizeof("ncedil")]; char entity_pool_str5358[sizeof("phiv")]; char entity_pool_str5375[sizeof("ic")]; char entity_pool_str5384[sizeof("capdot")]; char entity_pool_str5387[sizeof("dscy")]; char entity_pool_str5397[sizeof("check")]; char entity_pool_str5398[sizeof("ovbar")]; char entity_pool_str5405[sizeof("ntriangleleft")]; char entity_pool_str5411[sizeof("RightTee")]; char entity_pool_str5412[sizeof("nvge")]; char entity_pool_str5424[sizeof("leftrightsquigarrow")]; char entity_pool_str5431[sizeof("lozenge")]; char entity_pool_str5434[sizeof("RightTriangleBar")]; char entity_pool_str5436[sizeof("RightTeeVector")]; char entity_pool_str5438[sizeof("RightTriangleEqual")]; char entity_pool_str5439[sizeof("RightTriangle")]; char entity_pool_str5449[sizeof("Kcedil")]; char entity_pool_str5457[sizeof("Scedil")]; char entity_pool_str5468[sizeof("cirfnint")]; char entity_pool_str5471[sizeof("empty")]; char entity_pool_str5478[sizeof("afr")]; char entity_pool_str5482[sizeof("DiacriticalTilde")]; char entity_pool_str5489[sizeof("LeftDownVector")]; char entity_pool_str5492[sizeof("LeftDownVectorBar")]; char entity_pool_str5501[sizeof("lEg")]; char entity_pool_str5509[sizeof("ApplyFunction")]; char entity_pool_str5512[sizeof("bumpE")]; char entity_pool_str5524[sizeof("Lcedil")]; char entity_pool_str5528[sizeof("caret")]; char entity_pool_str5530[sizeof("Barv")]; char entity_pool_str5543[sizeof("Ccedil")]; char entity_pool_str5547[sizeof("circledR")]; char entity_pool_str5548[sizeof("LeftDownTeeVector")]; char entity_pool_str5552[sizeof("tshcy")]; char entity_pool_str5556[sizeof("DotEqual")]; char entity_pool_str5564[sizeof("centerdot")]; char entity_pool_str5566[sizeof("ntrianglelefteq")]; char entity_pool_str5568[sizeof("minus")]; char entity_pool_str5570[sizeof("gimel")]; char entity_pool_str5577[sizeof("Aacute")]; char entity_pool_str5578[sizeof("gtcir")]; char entity_pool_str5583[sizeof("gtrarr")]; char entity_pool_str5584[sizeof("bull")]; char entity_pool_str5587[sizeof("DownArrow")]; char entity_pool_str5593[sizeof("rdquor")]; char entity_pool_str5595[sizeof("ldquor")]; char entity_pool_str5598[sizeof("intlarhk")]; char entity_pool_str5602[sizeof("utilde")]; char entity_pool_str5612[sizeof("gacute")]; char entity_pool_str5614[sizeof("ntilde")]; char entity_pool_str5615[sizeof("af")]; char entity_pool_str5618[sizeof("Hstrok")]; char entity_pool_str5620[sizeof("exponentiale")]; char entity_pool_str5621[sizeof("minusb")]; char entity_pool_str5625[sizeof("RightUpTeeVector")]; char entity_pool_str5630[sizeof("UpTeeArrow")]; char entity_pool_str5639[sizeof("zeta")]; char entity_pool_str5644[sizeof("DiacriticalDot")]; char entity_pool_str5645[sizeof("DiacriticalDoubleAcute")]; char entity_pool_str5663[sizeof("nleftarrow")]; char entity_pool_str5664[sizeof("hkswarow")]; char entity_pool_str5666[sizeof("iiota")]; char entity_pool_str5669[sizeof("apacir")]; char entity_pool_str5673[sizeof("Ncedil")]; char entity_pool_str5678[sizeof("capand")]; char entity_pool_str5686[sizeof("mdash")]; char entity_pool_str5689[sizeof("filig")]; char entity_pool_str5690[sizeof("scnsim")]; char entity_pool_str5699[sizeof("realpart")]; char entity_pool_str5703[sizeof("leftthreetimes")]; char entity_pool_str5704[sizeof("asymp")]; char entity_pool_str5718[sizeof("hellip")]; char entity_pool_str5722[sizeof("dtrif")]; char entity_pool_str5724[sizeof("NotExists")]; char entity_pool_str5728[sizeof("sccue")]; char entity_pool_str5733[sizeof("YAcy")]; char entity_pool_str5734[sizeof("Utilde")]; char entity_pool_str5741[sizeof("NotEqual")]; char entity_pool_str5747[sizeof("ThinSpace")]; char entity_pool_str5754[sizeof("apE")]; char entity_pool_str5762[sizeof("bullet")]; char entity_pool_str5765[sizeof("CloseCurlyDoubleQuote")]; char entity_pool_str5766[sizeof("Delta")]; char entity_pool_str5776[sizeof("gg")]; char entity_pool_str5780[sizeof("otimes")]; char entity_pool_str5799[sizeof("wreath")]; char entity_pool_str5801[sizeof("Rcedil")]; char entity_pool_str5807[sizeof("eth")]; char entity_pool_str5808[sizeof("supnE")]; char entity_pool_str5811[sizeof("awint")]; char entity_pool_str5817[sizeof("Breve")]; char entity_pool_str5822[sizeof("Gg")]; char entity_pool_str5824[sizeof("HumpEqual")]; char entity_pool_str5837[sizeof("Lleftarrow")]; char entity_pool_str5838[sizeof("boxdr")]; char entity_pool_str5847[sizeof("succneqq")]; char entity_pool_str5848[sizeof("uring")]; char entity_pool_str5849[sizeof("LessSlantEqual")]; char entity_pool_str5860[sizeof("nvdash")]; char entity_pool_str5866[sizeof("Hacek")]; char entity_pool_str5867[sizeof("itilde")]; char entity_pool_str5870[sizeof("Iota")]; char entity_pool_str5872[sizeof("IOcy")]; char entity_pool_str5884[sizeof("boxDr")]; char entity_pool_str5891[sizeof("SucceedsTilde")]; char entity_pool_str5905[sizeof("LeftFloor")]; char entity_pool_str5906[sizeof("Vvdash")]; char entity_pool_str5923[sizeof("triangledown")]; char entity_pool_str5927[sizeof("LongLeftRightArrow")]; char entity_pool_str5928[sizeof("RightFloor")]; char entity_pool_str5931[sizeof("DownRightTeeVector")]; char entity_pool_str5933[sizeof("quatint")]; char entity_pool_str5937[sizeof("Ntilde")]; char entity_pool_str5940[sizeof("Bumpeq")]; char entity_pool_str5949[sizeof("gvnE")]; char entity_pool_str5951[sizeof("boxhu")]; char entity_pool_str5956[sizeof("gtlPar")]; char entity_pool_str5959[sizeof("nprec")]; char entity_pool_str5962[sizeof("ouml")]; char entity_pool_str5970[sizeof("gescc")]; char entity_pool_str5976[sizeof("Euml")]; char entity_pool_str5980[sizeof("Uring")]; char entity_pool_str5982[sizeof("UnderBracket")]; char entity_pool_str5983[sizeof("nLtv")]; char entity_pool_str5984[sizeof("LeftArrowBar")]; char entity_pool_str5985[sizeof("ncongdot")]; char entity_pool_str6003[sizeof("asympeq")]; char entity_pool_str6023[sizeof("minusdu")]; char entity_pool_str6030[sizeof("delta")]; char entity_pool_str6032[sizeof("harrw")]; char entity_pool_str6038[sizeof("andslope")]; char entity_pool_str6043[sizeof("cdot")]; char entity_pool_str6048[sizeof("Cayleys")]; char entity_pool_str6049[sizeof("boxhU")]; char entity_pool_str6052[sizeof("succsim")]; char entity_pool_str6061[sizeof("cirE")]; char entity_pool_str6062[sizeof("sdotb")]; char entity_pool_str6066[sizeof("odash")]; char entity_pool_str6067[sizeof("cirmid")]; char entity_pool_str6068[sizeof("suphsub")]; char entity_pool_str6069[sizeof("supdsub")]; char entity_pool_str6077[sizeof("supdot")]; char entity_pool_str6079[sizeof("awconint")]; char entity_pool_str6084[sizeof("TSHcy")]; char entity_pool_str6087[sizeof("grave")]; char entity_pool_str6101[sizeof("lsimg")]; char entity_pool_str6106[sizeof("UpArrowDownArrow")]; char entity_pool_str6121[sizeof("LeftVector")]; char entity_pool_str6122[sizeof("DoubleRightArrow")]; char entity_pool_str6129[sizeof("NegativeThinSpace")]; char entity_pool_str6140[sizeof("lhblk")]; char entity_pool_str6146[sizeof("cire")]; char entity_pool_str6147[sizeof("nVDash")]; char entity_pool_str6151[sizeof("uhblk")]; char entity_pool_str6155[sizeof("imagpart")]; char entity_pool_str6161[sizeof("RightUpDownVector")]; char entity_pool_str6164[sizeof("boxdL")]; char entity_pool_str6176[sizeof("gla")]; char entity_pool_str6193[sizeof("Iuml")]; char entity_pool_str6203[sizeof("oelig")]; char entity_pool_str6208[sizeof("NotLessSlantEqual")]; char entity_pool_str6210[sizeof("boxDL")]; char entity_pool_str6215[sizeof("gamma")]; char entity_pool_str6236[sizeof("Otimes")]; char entity_pool_str6248[sizeof("longleftrightarrow")]; char entity_pool_str6261[sizeof("Gamma")]; char entity_pool_str6262[sizeof("bigwedge")]; char entity_pool_str6268[sizeof("boxhd")]; char entity_pool_str6283[sizeof("supE")]; char entity_pool_str6292[sizeof("LeftUpTeeVector")]; char entity_pool_str6298[sizeof("gesdoto")]; char entity_pool_str6304[sizeof("kappa")]; char entity_pool_str6315[sizeof("ngeqslant")]; char entity_pool_str6340[sizeof("gtrless")]; char entity_pool_str6351[sizeof("fflig")]; char entity_pool_str6352[sizeof("bigsqcup")]; char entity_pool_str6367[sizeof("kgreen")]; char entity_pool_str6368[sizeof("supe")]; char entity_pool_str6370[sizeof("boxtimes")]; char entity_pool_str6386[sizeof("gnapprox")]; char entity_pool_str6394[sizeof("downdownarrows")]; char entity_pool_str6403[sizeof("biguplus")]; char entity_pool_str6404[sizeof("khcy")]; char entity_pool_str6406[sizeof("ddagger")]; char entity_pool_str6418[sizeof("Ouml")]; char entity_pool_str6420[sizeof("Beta")]; char entity_pool_str6421[sizeof("minusd")]; char entity_pool_str6422[sizeof("succnsim")]; char entity_pool_str6424[sizeof("ctdot")]; char entity_pool_str6427[sizeof("kjcy")]; char entity_pool_str6428[sizeof("gjcy")]; char entity_pool_str6430[sizeof("ncong")]; char entity_pool_str6431[sizeof("xvee")]; char entity_pool_str6432[sizeof("bcong")]; char entity_pool_str6439[sizeof("sqsube")]; char entity_pool_str6442[sizeof("boxdR")]; char entity_pool_str6445[sizeof("Longleftrightarrow")]; char entity_pool_str6447[sizeof("sqsub")]; char entity_pool_str6451[sizeof("DownLeftRightVector")]; char entity_pool_str6454[sizeof("sqsubset")]; char entity_pool_str6456[sizeof("NotVerticalBar")]; char entity_pool_str6461[sizeof("NotEqualTilde")]; char entity_pool_str6485[sizeof("boxdl")]; char entity_pool_str6488[sizeof("boxDR")]; char entity_pool_str6490[sizeof("andand")]; char entity_pool_str6502[sizeof("RightVector")]; char entity_pool_str6504[sizeof("IJlig")]; char entity_pool_str6505[sizeof("NotTildeEqual")]; char entity_pool_str6509[sizeof("angzarr")]; char entity_pool_str6515[sizeof("angrt")]; char entity_pool_str6521[sizeof("acd")]; char entity_pool_str6524[sizeof("andd")]; char entity_pool_str6526[sizeof("nrarrc")]; char entity_pool_str6527[sizeof("VeryThinSpace")]; char entity_pool_str6529[sizeof("Superset")]; char entity_pool_str6531[sizeof("boxDl")]; char entity_pool_str6535[sizeof("vnsub")]; char entity_pool_str6538[sizeof("ccupssm")]; char entity_pool_str6548[sizeof("varnothing")]; char entity_pool_str6552[sizeof("rcy")]; char entity_pool_str6554[sizeof("lcy")]; char entity_pool_str6556[sizeof("scy")]; char entity_pool_str6558[sizeof("Tcy")]; char entity_pool_str6559[sizeof("Zcy")]; char entity_pool_str6560[sizeof("ecy")]; char entity_pool_str6561[sizeof("rdsh")]; char entity_pool_str6563[sizeof("ldsh")]; char entity_pool_str6565[sizeof("ucy")]; char entity_pool_str6566[sizeof("boxVH")]; char entity_pool_str6567[sizeof("tcy")]; char entity_pool_str6577[sizeof("ncy")]; char entity_pool_str6579[sizeof("bcy")]; char entity_pool_str6580[sizeof("ntgl")]; char entity_pool_str6585[sizeof("Jcy")]; char entity_pool_str6600[sizeof("congdot")]; char entity_pool_str6607[sizeof("angst")]; char entity_pool_str6609[sizeof("RightDownTeeVector")]; char entity_pool_str6612[sizeof("OverParenthesis")]; char entity_pool_str6613[sizeof("ltquest")]; char entity_pool_str6615[sizeof("pcy")]; char entity_pool_str6618[sizeof("otilde")]; char entity_pool_str6619[sizeof("rdquo")]; char entity_pool_str6621[sizeof("ldquo")]; char entity_pool_str6623[sizeof("Vcy")]; char entity_pool_str6626[sizeof("capbrcup")]; char entity_pool_str6646[sizeof("bdquo")]; char entity_pool_str6650[sizeof("DownArrowBar")]; char entity_pool_str6657[sizeof("vcy")]; char entity_pool_str6665[sizeof("angrtvb")]; char entity_pool_str6676[sizeof("Kcy")]; char entity_pool_str6683[sizeof("Mcy")]; char entity_pool_str6684[sizeof("Scy")]; char entity_pool_str6691[sizeof("NewLine")]; char entity_pool_str6696[sizeof("fcy")]; char entity_pool_str6697[sizeof("Ucy")]; char entity_pool_str6704[sizeof("boxVh")]; char entity_pool_str6715[sizeof("Dcy")]; char entity_pool_str6738[sizeof("hstrok")]; char entity_pool_str6751[sizeof("Lcy")]; char entity_pool_str6762[sizeof("Ycy")]; char entity_pool_str6775[sizeof("supsim")]; char entity_pool_str6789[sizeof("NonBreakingSpace")]; char entity_pool_str6790[sizeof("OverBar")]; char entity_pool_str6791[sizeof("sqsubseteq")]; char entity_pool_str6797[sizeof("GJcy")]; char entity_pool_str6800[sizeof("OverBrace")]; char entity_pool_str6806[sizeof("eqcirc")]; char entity_pool_str6819[sizeof("OverBracket")]; char entity_pool_str6821[sizeof("Auml")]; char entity_pool_str6829[sizeof("acute")]; char entity_pool_str6830[sizeof("icy")]; char entity_pool_str6849[sizeof("Itilde")]; char entity_pool_str6850[sizeof("HilbertSpace")]; char entity_pool_str6854[sizeof("omega")]; char entity_pool_str6855[sizeof("cacute")]; char entity_pool_str6861[sizeof("scirc")]; char entity_pool_str6865[sizeof("ecirc")]; char entity_pool_str6870[sizeof("ucirc")]; char entity_pool_str6872[sizeof("GreaterSlantEqual")]; char entity_pool_str6890[sizeof("Jcirc")]; char entity_pool_str6895[sizeof("nvDash")]; char entity_pool_str6896[sizeof("Wcirc")]; char entity_pool_str6900[sizeof("Ncy")]; char entity_pool_str6921[sizeof("RightTeeArrow")]; char entity_pool_str6942[sizeof("LessFullEqual")]; char entity_pool_str6958[sizeof("ltcc")]; char entity_pool_str6963[sizeof("aleph")]; char entity_pool_str6979[sizeof("dcy")]; char entity_pool_str6989[sizeof("Scirc")]; char entity_pool_str6991[sizeof("lessapprox")]; char entity_pool_str7000[sizeof("IEcy")]; char entity_pool_str7001[sizeof("LowerRightArrow")]; char entity_pool_str7002[sizeof("Ucirc")]; char entity_pool_str7021[sizeof("agrave")]; char entity_pool_str7023[sizeof("MinusPlus")]; char entity_pool_str7024[sizeof("bigvee")]; char entity_pool_str7028[sizeof("Rcy")]; char entity_pool_str7034[sizeof("suphsol")]; char entity_pool_str7037[sizeof("EmptyVerySmallSquare")]; char entity_pool_str7039[sizeof("boxhD")]; char entity_pool_str7047[sizeof("precapprox")]; char entity_pool_str7066[sizeof("angrtvbd")]; char entity_pool_str7067[sizeof("Ycirc")]; char entity_pool_str7071[sizeof("sub")]; char entity_pool_str7074[sizeof("Otilde")]; char entity_pool_str7075[sizeof("Ccirc")]; char entity_pool_str7085[sizeof("Fcy")]; char entity_pool_str7090[sizeof("complexes")]; char entity_pool_str7096[sizeof("subrarr")]; char entity_pool_str7115[sizeof("InvisibleComma")]; char entity_pool_str7120[sizeof("boxur")]; char entity_pool_str7121[sizeof("abreve")]; char entity_pool_str7127[sizeof("ntlg")]; char entity_pool_str7135[sizeof("icirc")]; char entity_pool_str7142[sizeof("xdtri")]; char entity_pool_str7143[sizeof("circ")]; char entity_pool_str7168[sizeof("gtrdot")]; char entity_pool_str7171[sizeof("geqslant")]; char entity_pool_str7183[sizeof("ntriangleright")]; char entity_pool_str7198[sizeof("cuepr")]; char entity_pool_str7199[sizeof("Sub")]; char entity_pool_str7201[sizeof("mcy")]; char entity_pool_str7212[sizeof("timesbar")]; char entity_pool_str7214[sizeof("hksearow")]; char entity_pool_str7217[sizeof("sigma")]; char entity_pool_str7224[sizeof("cupor")]; char entity_pool_str7230[sizeof("oslash")]; char entity_pool_str7231[sizeof("dzigrarr")]; char entity_pool_str7234[sizeof("leftrightharpoons")]; char entity_pool_str7245[sizeof("rightleftharpoons")]; char entity_pool_str7247[sizeof("kcedil")]; char entity_pool_str7256[sizeof("submult")]; char entity_pool_str7260[sizeof("curren")]; char entity_pool_str7269[sizeof("LeftTeeVector")]; char entity_pool_str7274[sizeof("bigstar")]; char entity_pool_str7277[sizeof("cup")]; char entity_pool_str7278[sizeof("LongRightArrow")]; char entity_pool_str7294[sizeof("Gcedil")]; char entity_pool_str7296[sizeof("PrecedesEqual")]; char entity_pool_str7307[sizeof("zcy")]; char entity_pool_str7309[sizeof("planckh")]; char entity_pool_str7310[sizeof("Omega")]; char entity_pool_str7317[sizeof("subsub")]; char entity_pool_str7325[sizeof("rdca")]; char entity_pool_str7326[sizeof("cups")]; char entity_pool_str7327[sizeof("ldca")]; char entity_pool_str7332[sizeof("subset")]; char entity_pool_str7333[sizeof("NotSucceeds")]; char entity_pool_str7334[sizeof("LeftArrowRightArrow")]; char entity_pool_str7337[sizeof("wcirc")]; char entity_pool_str7338[sizeof("RightAngleBracket")]; char entity_pool_str7344[sizeof("ntrianglerighteq")]; char entity_pool_str7345[sizeof("Sigma")]; char entity_pool_str7350[sizeof("NotSucceedsTilde")]; char entity_pool_str7364[sizeof("DiacriticalAcute")]; char entity_pool_str7376[sizeof("subne")]; char entity_pool_str7378[sizeof("Product")]; char entity_pool_str7385[sizeof("circleddash")]; char entity_pool_str7389[sizeof("subsup")]; char entity_pool_str7397[sizeof("copy")]; char entity_pool_str7403[sizeof("eta")]; char entity_pool_str7409[sizeof("angmsd")]; char entity_pool_str7434[sizeof("natural")]; char entity_pool_str7436[sizeof("supedot")]; char entity_pool_str7437[sizeof("naturals")]; char entity_pool_str7443[sizeof("triangleright")]; char entity_pool_str7445[sizeof("DiacriticalGrave")]; char entity_pool_str7446[sizeof("boxuL")]; char entity_pool_str7447[sizeof("cong")]; char entity_pool_str7451[sizeof("telrec")]; char entity_pool_str7454[sizeof("comma")]; char entity_pool_str7460[sizeof("Subset")]; char entity_pool_str7475[sizeof("NotSucceedsSlantEqual")]; char entity_pool_str7476[sizeof("gtreqless")]; char entity_pool_str7477[sizeof("Atilde")]; char entity_pool_str7484[sizeof("curarr")]; char entity_pool_str7491[sizeof("cudarrr")]; char entity_pool_str7495[sizeof("cudarrl")]; char entity_pool_str7503[sizeof("subseteq")]; char entity_pool_str7504[sizeof("subseteqq")]; char entity_pool_str7505[sizeof("rightsquigarrow")]; char entity_pool_str7520[sizeof("cupcap")]; char entity_pool_str7521[sizeof("subsetneq")]; char entity_pool_str7532[sizeof("aogon")]; char entity_pool_str7533[sizeof("notinvc")]; char entity_pool_str7534[sizeof("rightthreetimes")]; char entity_pool_str7552[sizeof("yacute")]; char entity_pool_str7563[sizeof("nLeftarrow")]; char entity_pool_str7581[sizeof("ocy")]; char entity_pool_str7582[sizeof("cemptyv")]; char entity_pool_str7595[sizeof("Ecy")]; char entity_pool_str7598[sizeof("cupcup")]; char entity_pool_str7604[sizeof("trianglerighteq")]; char entity_pool_str7615[sizeof("LeftRightArrow")]; char entity_pool_str7618[sizeof("succ")]; char entity_pool_str7631[sizeof("DownArrowUpArrow")]; char entity_pool_str7641[sizeof("OElig")]; char entity_pool_str7648[sizeof("chcy")]; char entity_pool_str7649[sizeof("gtreqqless")]; char entity_pool_str7655[sizeof("angle")]; char entity_pool_str7662[sizeof("acE")]; char entity_pool_str7668[sizeof("rmoustache")]; char entity_pool_str7670[sizeof("lmoustache")]; char entity_pool_str7674[sizeof("NegativeVeryThinSpace")]; char entity_pool_str7677[sizeof("napprox")]; char entity_pool_str7686[sizeof("Oslash")]; char entity_pool_str7698[sizeof("subsetneqq")]; char entity_pool_str7723[sizeof("Aring")]; char entity_pool_str7724[sizeof("boxuR")]; char entity_pool_str7730[sizeof("subplus")]; char entity_pool_str7742[sizeof("xwedge")]; char entity_pool_str7767[sizeof("boxul")]; char entity_pool_str7778[sizeof("boxvr")]; char entity_pool_str7800[sizeof("HumpDownHump")]; char entity_pool_str7812[sizeof("Icy")]; char entity_pool_str7828[sizeof("approxeq")]; char entity_pool_str7841[sizeof("aacute")]; char entity_pool_str7842[sizeof("apid")]; char entity_pool_str7859[sizeof("UpDownArrow")]; char entity_pool_str7861[sizeof("NestedGreaterGreater")]; char entity_pool_str7863[sizeof("jcy")]; char entity_pool_str7866[sizeof("gtrsim")]; char entity_pool_str7876[sizeof("boxv")]; char entity_pool_str7886[sizeof("ocirc")]; char entity_pool_str7900[sizeof("Ecirc")]; char entity_pool_str7987[sizeof("notnivc")]; char entity_pool_str8006[sizeof("bigtriangleup")]; char entity_pool_str8032[sizeof("daleth")]; char entity_pool_str8037[sizeof("Ocy")]; char entity_pool_str8042[sizeof("Hcirc")]; char entity_pool_str8043[sizeof("RightVectorBar")]; char entity_pool_str8044[sizeof("AElig")]; char entity_pool_str8063[sizeof("FilledVerySmallSquare")]; char entity_pool_str8084[sizeof("ggg")]; char entity_pool_str8088[sizeof("Bcy")]; char entity_pool_str8099[sizeof("Poincareplane")]; char entity_pool_str8104[sizeof("boxvL")]; char entity_pool_str8107[sizeof("PartialD")]; char entity_pool_str8117[sizeof("Icirc")]; char entity_pool_str8129[sizeof("cularr")]; char entity_pool_str8135[sizeof("boxh")]; char entity_pool_str8142[sizeof("andv")]; char entity_pool_str8144[sizeof("sung")]; char entity_pool_str8148[sizeof("RightDoubleBracket")]; char entity_pool_str8168[sizeof("jcirc")]; char entity_pool_str8174[sizeof("UnderBar")]; char entity_pool_str8241[sizeof("RightArrow")]; char entity_pool_str8242[sizeof("circledcirc")]; char entity_pool_str8243[sizeof("Alpha")]; char entity_pool_str8251[sizeof("leftharpoonup")]; char entity_pool_str8258[sizeof("cularrp")]; char entity_pool_str8260[sizeof("RightArrowLeftArrow")]; char entity_pool_str8281[sizeof("varsigma")]; char entity_pool_str8300[sizeof("numero")]; char entity_pool_str8310[sizeof("ffllig")]; char entity_pool_str8326[sizeof("LowerLeftArrow")]; char entity_pool_str8340[sizeof("expectation")]; char entity_pool_str8342[sizeof("Ocirc")]; char entity_pool_str8351[sizeof("yacy")]; char entity_pool_str8375[sizeof("lambda")]; char entity_pool_str8381[sizeof("NotSucceedsEqual")]; char entity_pool_str8382[sizeof("boxvR")]; char entity_pool_str8384[sizeof("bigtriangledown")]; char entity_pool_str8391[sizeof("ang")]; char entity_pool_str8404[sizeof("xuplus")]; char entity_pool_str8424[sizeof("nabla")]; char entity_pool_str8425[sizeof("boxvl")]; char entity_pool_str8438[sizeof("Eta")]; char entity_pool_str8440[sizeof("Acy")]; char entity_pool_str8474[sizeof("kcy")]; char entity_pool_str8475[sizeof("gcy")]; char entity_pool_str8485[sizeof("LeftRightVector")]; char entity_pool_str8491[sizeof("ccedil")]; char entity_pool_str8495[sizeof("Backslash")]; char entity_pool_str8506[sizeof("hslash")]; char entity_pool_str8515[sizeof("Pcy")]; char entity_pool_str8521[sizeof("Gcy")]; char entity_pool_str8534[sizeof("gtquest")]; char entity_pool_str8572[sizeof("Lambda")]; char entity_pool_str8627[sizeof("odiv")]; char entity_pool_str8629[sizeof("leftharpoondown")]; char entity_pool_str8672[sizeof("longmapsto")]; char entity_pool_str8677[sizeof("Jukcy")]; char entity_pool_str8687[sizeof("ldrdhar")]; char entity_pool_str8700[sizeof("xutri")]; char entity_pool_str8701[sizeof("nRightarrow")]; char entity_pool_str8725[sizeof("ExponentialE")]; char entity_pool_str8735[sizeof("nrightarrow")]; char entity_pool_str8745[sizeof("Acirc")]; char entity_pool_str8746[sizeof("NoBreak")]; char entity_pool_str8780[sizeof("gcirc")]; char entity_pool_str8784[sizeof("ange")]; char entity_pool_str8785[sizeof("curarrm")]; char entity_pool_str8791[sizeof("SHCHcy")]; char entity_pool_str8796[sizeof("yuml")]; char entity_pool_str8800[sizeof("subnE")]; char entity_pool_str8803[sizeof("DDotrahd")]; char entity_pool_str8810[sizeof("RuleDelayed")]; char entity_pool_str8826[sizeof("Gcirc")]; char entity_pool_str8843[sizeof("Jsercy")]; char entity_pool_str8879[sizeof("gtcc")]; char entity_pool_str8922[sizeof("iukcy")]; char entity_pool_str8956[sizeof("updownarrow")]; char entity_pool_str8962[sizeof("curlyvee")]; char entity_pool_str8972[sizeof("ffilig")]; char entity_pool_str8992[sizeof("yicy")]; char entity_pool_str9015[sizeof("divonx")]; char entity_pool_str9026[sizeof("gtrapprox")]; char entity_pool_str9069[sizeof("subdot")]; char entity_pool_str9079[sizeof("leftrightarrows")]; char entity_pool_str9085[sizeof("auml")]; char entity_pool_str9088[sizeof("Updownarrow")]; char entity_pool_str9090[sizeof("rightleftarrows")]; char entity_pool_str9151[sizeof("DownRightVector")]; char entity_pool_str9154[sizeof("DownRightVectorBar")]; char entity_pool_str9162[sizeof("hcirc")]; char entity_pool_str9186[sizeof("Rrightarrow")]; char entity_pool_str9217[sizeof("longrightarrow")]; char entity_pool_str9239[sizeof("cupdot")]; char entity_pool_str9249[sizeof("ac")]; char entity_pool_str9268[sizeof("hookrightarrow")]; char entity_pool_str9271[sizeof("NegativeThickSpace")]; char entity_pool_str9275[sizeof("subE")]; char entity_pool_str9307[sizeof("twoheadrightarrow")]; char entity_pool_str9320[sizeof("downharpoonright")]; char entity_pool_str9321[sizeof("downharpoonleft")]; char entity_pool_str9326[sizeof("aelig")]; char entity_pool_str9330[sizeof("rdldhar")]; char entity_pool_str9349[sizeof("curlywedge")]; char entity_pool_str9351[sizeof("hybull")]; char entity_pool_str9360[sizeof("sube")]; char entity_pool_str9414[sizeof("Longrightarrow")]; char entity_pool_str9484[sizeof("Cedilla")]; char entity_pool_str9505[sizeof("notinva")]; char entity_pool_str9506[sizeof("SucceedsEqual")]; char entity_pool_str9554[sizeof("leftrightarrow")]; char entity_pool_str9580[sizeof("straightepsilon")]; char entity_pool_str9627[sizeof("amalg")]; char entity_pool_str9741[sizeof("atilde")]; char entity_pool_str9747[sizeof("RightCeiling")]; char entity_pool_str9751[sizeof("Leftrightarrow")]; char entity_pool_str9767[sizeof("subsim")]; char entity_pool_str9788[sizeof("VerticalLine")]; char entity_pool_str9801[sizeof("RightUpVector")]; char entity_pool_str9804[sizeof("RightUpVectorBar")]; char entity_pool_str9829[sizeof("RightDownVector")]; char entity_pool_str9832[sizeof("RightDownVectorBar")]; char entity_pool_str9836[sizeof("alefsym")]; char entity_pool_str9852[sizeof("circlearrowright")]; char entity_pool_str9853[sizeof("circlearrowleft")]; char entity_pool_str9904[sizeof("Iukcy")]; char entity_pool_str9936[sizeof("otimesas")]; char entity_pool_str9944[sizeof("intercal")]; char entity_pool_str9952[sizeof("thickapprox")]; char entity_pool_str9955[sizeof("jukcy")]; char entity_pool_str9959[sizeof("notniva")]; char entity_pool_str9963[sizeof("precnapprox")]; char entity_pool_str9983[sizeof("cuvee")]; char entity_pool_str9987[sizeof("aring")]; char entity_pool_str10023[sizeof("ccirc")]; char entity_pool_str10029[sizeof("rightarrow")]; char entity_pool_str10061[sizeof("Integral")]; char entity_pool_str10062[sizeof("xcirc")]; char entity_pool_str10121[sizeof("jsercy")]; char entity_pool_str10206[sizeof("checkmark")]; char entity_pool_str10208[sizeof("VerticalTilde")]; char entity_pool_str10219[sizeof("boxvH")]; char entity_pool_str10240[sizeof("NotRightTriangleBar")]; char entity_pool_str10244[sizeof("NotRightTriangleEqual")]; char entity_pool_str10245[sizeof("NotRightTriangle")]; char entity_pool_str10278[sizeof("LeftVectorBar")]; char entity_pool_str10357[sizeof("boxvh")]; char entity_pool_str10395[sizeof("boxbox")]; char entity_pool_str10415[sizeof("ycy")]; char entity_pool_str10428[sizeof("subedot")]; char entity_pool_str10445[sizeof("SOFTcy")]; char entity_pool_str10505[sizeof("Rightarrow")]; char entity_pool_str10507[sizeof("alpha")]; char entity_pool_str10528[sizeof("shchcy")]; char entity_pool_str10584[sizeof("softcy")]; char entity_pool_str10704[sizeof("acy")]; char entity_pool_str10720[sizeof("ycirc")]; char entity_pool_str10791[sizeof("bigcirc")]; char entity_pool_str10808[sizeof("ImaginaryI")]; char entity_pool_str10847[sizeof("approx")]; char entity_pool_str10851[sizeof("SupersetEqual")]; char entity_pool_str10879[sizeof("vzigzag")]; char entity_pool_str10888[sizeof("cuesc")]; char entity_pool_str10947[sizeof("UnderParenthesis")]; char entity_pool_str11009[sizeof("acirc")]; char entity_pool_str11029[sizeof("succapprox")]; char entity_pool_str11047[sizeof("mcomma")]; char entity_pool_str11146[sizeof("angmsdae")]; char entity_pool_str11165[sizeof("angmsdab")]; char entity_pool_str11282[sizeof("angmsdaf")]; char entity_pool_str11366[sizeof("angsph")]; char entity_pool_str11527[sizeof("luruhar")]; char entity_pool_str11565[sizeof("angmsdad")]; char entity_pool_str11664[sizeof("twoheadleftarrow")]; char entity_pool_str11720[sizeof("cylcty")]; char entity_pool_str11791[sizeof("straightphi")]; char entity_pool_str11840[sizeof("multimap")]; char entity_pool_str11918[sizeof("RightArrowBar")]; char entity_pool_str12012[sizeof("ldrushar")]; char entity_pool_str12103[sizeof("LeftAngleBracket")]; char entity_pool_str12170[sizeof("ruluhar")]; char entity_pool_str12202[sizeof("curlyeqprec")]; char entity_pool_str12206[sizeof("yucy")]; char entity_pool_str12288[sizeof("lurdshar")]; char entity_pool_str12413[sizeof("hardcy")]; char entity_pool_str12461[sizeof("rightharpoondown")]; char entity_pool_str12497[sizeof("rightharpoonup")]; char entity_pool_str12502[sizeof("HARDcy")]; char entity_pool_str12651[sizeof("SubsetEqual")]; char entity_pool_str12809[sizeof("digamma")]; char entity_pool_str12892[sizeof("udblac")]; char entity_pool_str12985[sizeof("SuchThat")]; char entity_pool_str12991[sizeof("cuwed")]; char entity_pool_str13024[sizeof("Udblac")]; char entity_pool_str13061[sizeof("angmsdag")]; char entity_pool_str13443[sizeof("angmsdah")]; char entity_pool_str13643[sizeof("VerticalBar")]; char entity_pool_str13659[sizeof("VerticalSeparator")]; char entity_pool_str13709[sizeof("rightarrowtail")]; char entity_pool_str13908[sizeof("odblac")]; char entity_pool_str13945[sizeof("succnapprox")]; char entity_pool_str14304[sizeof("angmsdac")]; char entity_pool_str14364[sizeof("Odblac")]; char entity_pool_str14620[sizeof("cupbrcap")]; char entity_pool_str15290[sizeof("angmsdaa")]; char entity_pool_str15360[sizeof("curlyeqsucc")]; char entity_pool_str15729[sizeof("curvearrowleft")]; char entity_pool_str16000[sizeof("curvearrowright")]; }; static const struct entity_pool_t entity_pool_contents = { "rarr", "larr", "lat", "uarr", "npr", "rarrtl", "larrtl", "roarr", "loarr", "not", "rpar", "bot", "lpar", "spar", "ll", "uharr", "epar", "el", "rotimes", "lotimes", "par", "nharr", "npar", "tprime", "els", "eparsl", "ensp", "bprime", "lnap", "blk14", "blk12", "blk34", "nparsl", "nldr", "rlarr", "npart", "llarr", "nlt", "slarr", "nparallel", "Tau", "varr", "squ", "nlarr", "tau", "lne", "rrarr", "lrarr", "srarr", "rharul", "lharul", "erarr", "pr", "rharu", "lharu", "Uarr", "nGt", "bne", "nrarr", "swarr", "rarrap", "upuparrows", "Darr", "rbarr", "Dot", "lbarr", "nwarr", "smt", "emsp14", "rarrpl", "larrpl", "phmmat", "emsp13", "LT", "Larr", "rbrkslu", "lbrkslu", "napos", "nle", "rHar", "lHar", "qprime", "lap", "nbsp", "uHar", "top", "Vbar", "Ll", "prap", "emsp", "nap", "looparrowleft", "le", "sharp", "ee", "les", "in", "prop", "topbot", "int", "ne", "nprcue", "pre", "epsi", "upsi", "there4", "rbrke", "searr", "lbrke", "blacktriangle", "lneq", "lneqq", "plus", "nles", "nedot", "blacktriangleleft", "blacktriangleright", "nearr", "blacktriangledown", "nless", "emacr", "vprop", "umacr", "smeparsl", "Map", "plusdu", "Not", "Verbar", "perp", "fltns", "plusmn", "nleq", "nleqq", "frac34", "frac14", "verbar", "frac12", "frac35", "frac15", "frac45", "frac25", "frac13", "frac16", "prurel", "frac23", "frac38", "frac18", "frac56", "frac58", "frac78", "leq", "darr", "Upsi", "dot", "phone", "Cap", "blacksquare", "rnmid", "leqq", "intcal", "dharr", "rhard", "lhard", "pluse", "Umacr", "Vee", "Rarr", "Cross", "rsqb", "lsqb", "Rarrtl", "esdot", "vee", "nbumpe", "llcorner", "fpartint", "squf", "plankv", "eqvparsl", "ulcorner", "wp", "lozf", "COPY", "ulcorn", "veebar", "part", "square", "nbump", "bernou", "wr", "rBarr", "lrcorner", "lBarr", "bnot", "semi", "urcorner", "NotSubset", "ropf", "Qopf", "lopf", "sopf", "urcorn", "Topf", "Zopf", "eopf", "ropar", "uopf", "lopar", "topf", "Xopf", "nopf", "bopf", "epsiv", "fnof", "imacr", "Jopf", "nhpar", "Wopf", "Sqrt", "nsub", "napid", "NotSuperset", "brvbar", "sol", "easter", "popf", "dHar", "Vopf", "nsupset", "nsup", "vBar", "nsubset", "thkap", "nis", "profsurf", "solb", "lnsim", "solbar", "Square", "vopf", "uharl", "ulcrop", "eqsim", "equiv", "ell", "smashp", "mp", "Kopf", "simrarr", "flat", "Mopf", "Sopf", "mldr", "rlm", "iprod", "lparlt", "fopf", "Uopf", "varsubsetneq", "varsubsetneqq", "urcrop", "LessLess", "Re", "NotNestedLessLess", "Dopf", "forkv", "nsqsube", "nsupe", "nsube", "qopf", "rlhar", "lrm", "nlsim", "pound", "varsupsetneq", "varsupsetneqq", "bnequiv", "Lopf", "nsqsupe", "rarrlp", "wedbar", "larrlp", "Yopf", "NotReverseElement", "Copf", "lrhar", "parsl", "uml", "marker", "nsupseteq", "nsubseteq", "squarf", "Vert", "SquareSupersetEqual", "prsim", "SquareSubsetEqual", "SquareSuperset", "SquareSubset", "nvap", "iopf", "pm", "vert", "thetav", "loz", "map", "lesseqqgtr", "rscr", "Qscr", "lscr", "sscr", "Tscr", "Zscr", "escr", "uscr", "tscr", "imof", "Coproduct", "Xscr", "Xi", "nscr", "ni", "bscr", "Nopf", "Jscr", "preceq", "nvrArr", "backprime", "Wscr", "varphi", "nsmid", "dlcorn", "pscr", "pi", "Vscr", "nesim", "simne", "nsupseteqq", "nsubseteqq", "drcorn", "rbrace", "vscr", "lbrace", "dopf", "frasl", "LessTilde", "Kscr", "pluscir", "Mscr", "Sscr", "rbrksld", "lbrksld", "RBarr", "sqcaps", "rArr", "bNot", "lArr", "fscr", "Uscr", "uArr", "Ropf", "wopf", "Dscr", "opar", "seswar", "Del", "rAarr", "rho", "lAarr", "preccurlyeq", "qscr", "macr", "notin", "equivDD", "sqcap", "nspar", "olt", "ratio", "Lscr", "dharl", "dlcrop", "DoubleDot", "dotplus", "or", "Yscr", "Fopf", "Cscr", "olarr", "nrarrw", "lvertneqq", "eqslantgtr", "thorn", "eqslantless", "incare", "vArr", "rppolint", "drcrop", "parallel", "orarr", "ssmile", "DoubleLeftTee", "erDot", "diams", "ssetmn", "oS", "iscr", "ii", "rect", "nsccue", "sect", "mlcp", "oror", "DoubleContourIntegral", "equals", "Hat", "sstarf", "mstpos", "die", "measuredangle", "forall", "notinvb", "mopf", "niv", "vBarv", "Nscr", "period", "becaus", "between", "Int", "because", "piv", "rfr", "Qfr", "lfr", "sfr", "nleftrightarrow", "Tfr", "Zfr", "efr", "sim", "ufr", "roplus", "tfr", "loplus", "Xfr", "real", "nfr", "bfr", "NotHumpEqual", "Jfr", "dscr", "Wfr", "blacklozenge", "zopf", "reals", "NotCupCap", "simplus", "ForAll", "pfr", "omacr", "Vfr", "Emacr", "Rscr", "wscr", "ShortUpArrow", "setmn", "vfr", "Kfr", "operp", "Mfr", "Sfr", "nltrie", "Fscr", "ffr", "Ufr", "shortmid", "nvsim", "Dfr", "lessdot", "profline", "qfr", "dArr", "nrtrie", "ShortRightArrow", "Therefore", "DD", "therefore", "Lfr", "target", "Element", "Yfr", "ClockwiseContourIntegral", "olcir", "Cfr", "female", "nsucceq", "oast", "percnt", "ordf", "ord", "Rho", "mscr", "nvrtrie", "lnE", "nhArr", "Or", "divide", "ifr", "elinters", "bsol", "nvlArr", "Imacr", "backsimeq", "twixt", "olcross", "rarrsim", "DoubleDownArrow", "larrsim", "emptyset", "oopf", "exist", "llhard", "excl", "Eopf", "nlArr", "thinsp", "NotSubsetEqual", "phi", "DoubleLeftArrow", "topcir", "div", "Nfr", "nlE", "zscr", "lrhard", "lltri", "nrArr", "NotSupersetEqual", "swArr", "ThickSpace", "ultri", "notnivb", "prime", "primes", "ohm", "CircleTimes", "nltri", "siml", "nwArr", "varpi", "orv", "setminus", "lrtri", "permil", "mid", "urtri", "dfr", "mho", "prE", "vsupne", "nrtri", "vsubne", "eDot", "lesges", "backepsilon", "ratail", "latail", "UpEquilibrium", "epsilon", "upsilon", "midast", "Hopf", "vltri", "Rfr", "Wedge", "wfr", "barwed", "malt", "Chi", "emptyv", "notni", "LessGreater", "diam", "vrtri", "CircleMinus", "Omacr", "seArr", "Ffr", "precneqq", "Diamond", "ordm", "neArr", "Iopf", "CircleDot", "prnap", "dotminus", "nshortmid", "bottom", "pointint", "SquareUnion", "jopf", "Upsilon", "Colone", "nvlt", "NestedLessLess", "Colon", "bsolhsub", "DoubleLeftRightArrow", "plussim", "image", "egs", "oscr", "swnwar", "zeetrf", "maltese", "mfr", "rarrfs", "Escr", "larrfs", "mnplus", "ngt", "ngtr", "gl", "diamondsuit", "GT", "lesssim", "dsol", "upharpoonleft", "SquareIntersection", "lsime", "nLt", "NotLess", "gnap", "scap", "mapstoleft", "NotLessLess", "rfloor", "lfloor", "nsime", "bsime", "NotLessEqual", "NotLessTilde", "ncap", "NotLessGreater", "precsim", "looparrowright", "Pr", "rcub", "mapstoup", "lcub", "zfr", "uparrow", "gne", "sce", "Im", "rcaron", "lcaron", "Oopf", "scaron", "backsim", "Tcaron", "Zcaron", "ecaron", "Bernoullis", "nge", "tcaron", "fork", "Hscr", "ncaron", "elsdot", "tbrk", "triplus", "diamond", "ncup", "bbrk", "frown", "bkarow", "spades", "psi", "Bopf", "dollar", "disin", "spadesuit", "NotTilde", "doublebarwedge", "gap", "bbrktbrk", "swarrow", "bepsi", "Iscr", "NotTildeFullEqual", "eqcolon", "tint", "intprod", "nsupE", "nwarrow", "nsubE", "nges", "Uparrow", "ge", "OpenCurlyDoubleQuote", "smallsetminus", "Scaron", "nvltrie", "ges", "blank", "QUOT", "block", "trade", "jscr", "wedge", "Amacr", "Equal", "Dcaron", "DotDot", "gneq", "varpropto", "gneqq", "Proportional", "isins", "eDDot", "isin", "TripleDot", "Fouriertrf", "Proportion", "ngeq", "Lcaron", "ngeqq", "lE", "Ccaron", "bsemi", "propto", "lesdot", "Conint", "And", "searrow", "orslope", "harr", "late", "CenterDot", "ofr", "nearrow", "qint", "lates", "kappav", "horbar", "Efr", "hoarr", "npre", "inodot", "udarr", "geq", "nsimeq", "geqq", "efDot", "rpargt", "Oscr", "plusdo", "lagran", "thicksim", "precnsim", "Ncaron", "napE", "iiint", "Bscr", "mapstodown", "varrho", "isinsv", "nvHarr", "NotLeftTriangleBar", "equest", "NotLeftTriangleEqual", "NotLeftTriangle", "Aopf", "hbar", "vangrt", "Hfr", "range", "smte", "lsim", "npolint", "dcaron", "esim", "Union", "smtes", "kopf", "gopf", "nsim", "bsim", "SmallCircle", "NotDoubleVerticalBar", "NotNestedGreaterGreater", "EqualTilde", "notindot", "Rcaron", "Popf", "Gopf", "Ifr", "wedgeq", "prod", "osol", "DoubleUpArrow", "Congruent", "gnsim", "scsim", "jfr", "upsih", "nLl", "DoubleUpDownArrow", "ngsim", "hearts", "lesseqgtr", "nesear", "Exists", "smile", "uwangle", "heartsuit", "HorizontalLine", "GreaterLess", "rsaquo", "lsaquo", "realine", "Dashv", "simdot", "GreaterEqual", "GreaterTilde", "GreaterEqualLess", "GreaterGreater", "rceil", "lceil", "lessgtr", "oline", "thksim", "InvisibleTimes", "race", "iquest", "imagline", "UpTee", "midcir", "ofcir", "ddarr", "rangd", "langd", "Equilibrium", "parsim", "Vdashl", "Ofr", "Because", "rAtail", "lAtail", "ominus", "Ascr", "Epsilon", "ShortLeftArrow", "isinv", "micro", "zcaron", "kscr", "gscr", "Bfr", "gel", "hercon", "triminus", "egrave", "sdot", "ugrave", "Zdot", "edot", "NotTildeTilde", "tdot", "Pscr", "Pi", "Gscr", "plustwo", "NotElement", "PlusMinus", "hopf", "gammad", "mDDot", "divideontimes", "doteq", "varepsilon", "Precedes", "Gammad", "dashv", "NotCongruent", "ubreve", "ogt", "RoundImplies", "PrecedesSlantEqual", "sime", "Ugrave", "dbkarow", "sdote", "veeeq", "mapsto", "times", "rangle", "langle", "leftarrowtail", "hamilt", "udhar", "nisd", "rfisht", "lfisht", "harrcir", "OpenCurlyQuote", "ufisht", "NotHumpDownHump", "LeftTee", "rsh", "lsh", "gvertneqq", "timesb", "scpolint", "Cdot", "dwangle", "Ubreve", "LeftUpVector", "LeftUpVectorBar", "Ecaron", "homtht", "igrave", "npreceq", "ecolon", "dd", "simeq", "notinE", "bigoplus", "Afr", "leftarrow", "oint", "Tab", "ogon", "lt", "nLeftrightarrow", "rarrb", "larrb", "hscr", "LeftUpDownVector", "kfr", "gfr", "UpArrowBar", "nsce", "ltdot", "gesl", "xodot", "star", "lowbar", "xharr", "ecir", "utdot", "natur", "Lsh", "infin", "comp", "sigmav", "xotime", "Pfr", "Gfr", "bigcap", "simlE", "iiiint", "barwedge", "Barwed", "xlarr", "LessEqualGreater", "crarr", "isindot", "commat", "middot", "lesdotor", "sigmaf", "rarrbfs", "larrbfs", "xrarr", "bigcup", "clubs", "hArr", "rtrie", "ltrie", "imped", "eogon", "rx", "ltrPar", "Star", "uogon", "Tilde", "half", "tilde", "Leftarrow", "gesles", "cap", "strns", "Lt", "prnE", "sqsupe", "sqsupset", "tridot", "order", "caps", "cross", "dfisht", "xmap", "sqsup", "rtri", "ltri", "it", "rmoust", "lmoust", "gnE", "lgE", "scE", "utri", "vellip", "ETH", "lmidot", "Uogon", "CounterClockwiseContourIntegral", "ngE", "nwnear", "lesg", "plusb", "Rsh", "copysr", "infintie", "imath", "Esim", "Phi", "glE", "vnsup", "simgE", "DoubleLongLeftArrow", "DoubleLongLeftRightArrow", "nvgt", "Mellintrf", "Prime", "iinfin", "ReverseElement", "EmptySmallSquare", "radic", "hfr", "zdot", "male", "rarrc", "prec", "scnap", "DifferentialD", "models", "ltcir", "iogon", "capcap", "iff", "ddotseq", "CirclePlus", "rthree", "lthree", "PrecedesTilde", "dtdot", "clubsuit", "racute", "lacute", "trpezium", "sacute", "Zacute", "eacute", "TildeTilde", "Uarrocir", "uacute", "lowast", "nacute", "NotPrecedes", "Lmidot", "UpArrow", "rarrw", "DownTee", "FilledSmallSquare", "capcup", "GreaterFullEqual", "nvle", "trie", "omicron", "DoubleRightTee", "Cconint", "rsquor", "lsquor", "zigrarr", "copf", "ContourIntegral", "hairsp", "sqsupseteq", "csub", "upharpoonright", "DownBreve", "ShortDownArrow", "xopf", "Sacute", "vsupnE", "cir", "plusacir", "csup", "vsubnE", "Uacute", "isinE", "gEl", "sqcups", "smid", "lg", "DoubleLongRightArrow", "NotPrecedesSlantEqual", "eg", "AMP", "nmid", "timesd", "DownLeftVector", "zwnj", "Lacute", "DownLeftVectorBar", "ograve", "Yacute", "sqcup", "odot", "Cacute", "nu", "tritime", "Egrave", "eplus", "backcong", "uplus", "Edot", "csupe", "simg", "UpperRightArrow", "csube", "dtri", "prnsim", "boxUr", "uuarr", "DownLeftTeeVector", "gsime", "bigotimes", "Dagger", "Intersection", "iacute", "prcue", "egsdot", "Implies", "VDash", "bump", "Mu", "vDash", "lvnE", "LeftTeeArrow", "Nacute", "UnderBrace", "Psi", "rhov", "lescc", "sup1", "sup2", "sup3", "bigodot", "Downarrow", "xsqcup", "barvee", "NegativeMediumSpace", "bumpe", "cscr", "nsc", "sup", "cedil", "boxVr", "origof", "zwj", "Igrave", "Idot", "xscr", "xi", "nGtv", "boxHu", "THORN", "Racute", "rarrhk", "larrhk", "rtriltri", "boxV", "dagger", "Omicron", "DoubleVerticalBar", "nexists", "Nu", "nexist", "gE", "ap", "Sup", "doteqdot", "eng", "caron", "boxHU", "gesdot", "ReverseEquilibrium", "boxUL", "supmult", "pitchfork", "numsp", "rang", "lang", "ocir", "rationals", "coprod", "ltlarr", "breve", "nang", "swarhk", "raquo", "laquo", "supsub", "Cup", "ape", "quest", "nwarhk", "supset", "downarrow", "duarr", "apos", "Ograve", "shortparallel", "nsucc", "LongLeftArrow", "lesdoto", "supne", "nGg", "raemptyv", "supsup", "laemptyv", "topfork", "Eogon", "risingdotseq", "bumpeq", "lstrok", "Tstrok", "gsim", "bemptyv", "zacute", "gsiml", "tstrok", "roang", "boxVL", "loang", "nleqslant", "sbquo", "searhk", "lnapprox", "Supset", "boxHd", "varkappa", "circeq", "yopf", "UnionPlus", "Lang", "nearhk", "shcy", "cfr", "Kappa", "ljcy", "MediumSpace", "supseteq", "supseteqq", "reg", "amacr", "leg", "weierp", "TScy", "supsetneq", "njcy", "xfr", "mu", "nvinfin", "boxUR", "xoplus", "leftleftarrows", "sum", "beth", "complement", "num", "amp", "boxUl", "NotGreater", "boxplus", "jmath", "sfrown", "Dstrok", "and", "NotGreaterGreater", "NotGreaterSlantEqual", "NotGreaterLess", "quot", "NotGreaterFullEqual", "hyphen", "planck", "TildeEqual", "tosa", "Lstrok", "shy", "xnis", "Iogon", "DZcy", "ohbar", "cirscir", "sext", "para", "ast", "questeq", "Sum", "DScy", "ENG", "ZHcy", "longleftarrow", "dash", "DownTeeArrow", "supsetneqq", "profalar", "oacute", "boxVR", "Eacute", "supplus", "hookleftarrow", "CloseCurlyQuote", "trisb", "dotsquare", "rtimes", "ltimes", "toea", "Agrave", "Assign", "Rang", "iocy", "NotPrecedesEqual", "aopf", "chi", "quaternions", "boxVl", "NotGreaterEqual", "xhArr", "orderof", "rsquo", "lsquo", "yscr", "gdot", "NotSquareSubsetEqual", "KHcy", "bsolb", "NotSquareSubset", "SHcy", "YIcy", "cwint", "Theta", "theta", "xlArr", "NotSquareSupersetEqual", "demptyv", "triangle", "Gdot", "NotSquareSuperset", "Abreve", "dstrok", "pertenk", "rbrack", "lbrack", "odsold", "omid", "xrArr", "triangleleft", "NotGreaterTilde", "colone", "Longleftarrow", "iota", "colon", "Zeta", "gbreve", "CHcy", "YUcy", "REG", "szlig", "dzcy", "beta", "euro", "LeftArrow", "CapitalDifferentialD", "ring", "Laplacetrf", "djcy", "oplus", "integers", "Gbreve", "ubrcy", "euml", "deg", "uuml", "Iacute", "succeq", "KJcy", "CupCap", "tscy", "cent", "DJcy", "TildeFullEqual", "triangleq", "duhar", "LeftDoubleBracket", "LJcy", "iecy", "trianglelefteq", "nequiv", "nshortparallel", "ndash", "bowtie", "fjlig", "Ubrcy", "vartheta", "Uuml", "vartriangleright", "vartriangleleft", "ascr", "succcurlyeq", "cwconint", "sc", "fllig", "circledast", "Vdash", "nVdash", "suplarr", "robrk", "lobrk", "vdash", "Yuml", "gt", "ccaps", "Succeeds", "Oacute", "TRADE", "NJcy", "gtdot", "yfr", "compfn", "Gt", "scnE", "ijlig", "circledS", "yen", "thetasym", "iuml", "SucceedsSlantEqual", "boxH", "mumap", "rightrightarrows", "coloneq", "Sc", "glj", "iexcl", "ccups", "xcap", "zhcy", "boxHD", "leqslant", "UpperLeftArrow", "dblac", "puncsp", "ccaron", "rbbrk", "lbbrk", "Aogon", "LeftTriangleBar", "gesdotol", "LeftTriangleEqual", "LeftTriangle", "conint", "drbkarow", "rtrif", "ltrif", "ReverseUpEquilibrium", "LeftCeiling", "utrif", "xcup", "fallingdotseq", "rcedil", "lcedil", "scedil", "Tcedil", "starf", "boxminus", "tcedil", "ZeroWidthSpace", "ncedil", "phiv", "ic", "capdot", "dscy", "check", "ovbar", "ntriangleleft", "RightTee", "nvge", "leftrightsquigarrow", "lozenge", "RightTriangleBar", "RightTeeVector", "RightTriangleEqual", "RightTriangle", "Kcedil", "Scedil", "cirfnint", "empty", "afr", "DiacriticalTilde", "LeftDownVector", "LeftDownVectorBar", "lEg", "ApplyFunction", "bumpE", "Lcedil", "caret", "Barv", "Ccedil", "circledR", "LeftDownTeeVector", "tshcy", "DotEqual", "centerdot", "ntrianglelefteq", "minus", "gimel", "Aacute", "gtcir", "gtrarr", "bull", "DownArrow", "rdquor", "ldquor", "intlarhk", "utilde", "gacute", "ntilde", "af", "Hstrok", "exponentiale", "minusb", "RightUpTeeVector", "UpTeeArrow", "zeta", "DiacriticalDot", "DiacriticalDoubleAcute", "nleftarrow", "hkswarow", "iiota", "apacir", "Ncedil", "capand", "mdash", "filig", "scnsim", "realpart", "leftthreetimes", "asymp", "hellip", "dtrif", "NotExists", "sccue", "YAcy", "Utilde", "NotEqual", "ThinSpace", "apE", "bullet", "CloseCurlyDoubleQuote", "Delta", "gg", "otimes", "wreath", "Rcedil", "eth", "supnE", "awint", "Breve", "Gg", "HumpEqual", "Lleftarrow", "boxdr", "succneqq", "uring", "LessSlantEqual", "nvdash", "Hacek", "itilde", "Iota", "IOcy", "boxDr", "SucceedsTilde", "LeftFloor", "Vvdash", "triangledown", "LongLeftRightArrow", "RightFloor", "DownRightTeeVector", "quatint", "Ntilde", "Bumpeq", "gvnE", "boxhu", "gtlPar", "nprec", "ouml", "gescc", "Euml", "Uring", "UnderBracket", "nLtv", "LeftArrowBar", "ncongdot", "asympeq", "minusdu", "delta", "harrw", "andslope", "cdot", "Cayleys", "boxhU", "succsim", "cirE", "sdotb", "odash", "cirmid", "suphsub", "supdsub", "supdot", "awconint", "TSHcy", "grave", "lsimg", "UpArrowDownArrow", "LeftVector", "DoubleRightArrow", "NegativeThinSpace", "lhblk", "cire", "nVDash", "uhblk", "imagpart", "RightUpDownVector", "boxdL", "gla", "Iuml", "oelig", "NotLessSlantEqual", "boxDL", "gamma", "Otimes", "longleftrightarrow", "Gamma", "bigwedge", "boxhd", "supE", "LeftUpTeeVector", "gesdoto", "kappa", "ngeqslant", "gtrless", "fflig", "bigsqcup", "kgreen", "supe", "boxtimes", "gnapprox", "downdownarrows", "biguplus", "khcy", "ddagger", "Ouml", "Beta", "minusd", "succnsim", "ctdot", "kjcy", "gjcy", "ncong", "xvee", "bcong", "sqsube", "boxdR", "Longleftrightarrow", "sqsub", "DownLeftRightVector", "sqsubset", "NotVerticalBar", "NotEqualTilde", "boxdl", "boxDR", "andand", "RightVector", "IJlig", "NotTildeEqual", "angzarr", "angrt", "acd", "andd", "nrarrc", "VeryThinSpace", "Superset", "boxDl", "vnsub", "ccupssm", "varnothing", "rcy", "lcy", "scy", "Tcy", "Zcy", "ecy", "rdsh", "ldsh", "ucy", "boxVH", "tcy", "ncy", "bcy", "ntgl", "Jcy", "congdot", "angst", "RightDownTeeVector", "OverParenthesis", "ltquest", "pcy", "otilde", "rdquo", "ldquo", "Vcy", "capbrcup", "bdquo", "DownArrowBar", "vcy", "angrtvb", "Kcy", "Mcy", "Scy", "NewLine", "fcy", "Ucy", "boxVh", "Dcy", "hstrok", "Lcy", "Ycy", "supsim", "NonBreakingSpace", "OverBar", "sqsubseteq", "GJcy", "OverBrace", "eqcirc", "OverBracket", "Auml", "acute", "icy", "Itilde", "HilbertSpace", "omega", "cacute", "scirc", "ecirc", "ucirc", "GreaterSlantEqual", "Jcirc", "nvDash", "Wcirc", "Ncy", "RightTeeArrow", "LessFullEqual", "ltcc", "aleph", "dcy", "Scirc", "lessapprox", "IEcy", "LowerRightArrow", "Ucirc", "agrave", "MinusPlus", "bigvee", "Rcy", "suphsol", "EmptyVerySmallSquare", "boxhD", "precapprox", "angrtvbd", "Ycirc", "sub", "Otilde", "Ccirc", "Fcy", "complexes", "subrarr", "InvisibleComma", "boxur", "abreve", "ntlg", "icirc", "xdtri", "circ", "gtrdot", "geqslant", "ntriangleright", "cuepr", "Sub", "mcy", "timesbar", "hksearow", "sigma", "cupor", "oslash", "dzigrarr", "leftrightharpoons", "rightleftharpoons", "kcedil", "submult", "curren", "LeftTeeVector", "bigstar", "cup", "LongRightArrow", "Gcedil", "PrecedesEqual", "zcy", "planckh", "Omega", "subsub", "rdca", "cups", "ldca", "subset", "NotSucceeds", "LeftArrowRightArrow", "wcirc", "RightAngleBracket", "ntrianglerighteq", "Sigma", "NotSucceedsTilde", "DiacriticalAcute", "subne", "Product", "circleddash", "subsup", "copy", "eta", "angmsd", "natural", "supedot", "naturals", "triangleright", "DiacriticalGrave", "boxuL", "cong", "telrec", "comma", "Subset", "NotSucceedsSlantEqual", "gtreqless", "Atilde", "curarr", "cudarrr", "cudarrl", "subseteq", "subseteqq", "rightsquigarrow", "cupcap", "subsetneq", "aogon", "notinvc", "rightthreetimes", "yacute", "nLeftarrow", "ocy", "cemptyv", "Ecy", "cupcup", "trianglerighteq", "LeftRightArrow", "succ", "DownArrowUpArrow", "OElig", "chcy", "gtreqqless", "angle", "acE", "rmoustache", "lmoustache", "NegativeVeryThinSpace", "napprox", "Oslash", "subsetneqq", "Aring", "boxuR", "subplus", "xwedge", "boxul", "boxvr", "HumpDownHump", "Icy", "approxeq", "aacute", "apid", "UpDownArrow", "NestedGreaterGreater", "jcy", "gtrsim", "boxv", "ocirc", "Ecirc", "notnivc", "bigtriangleup", "daleth", "Ocy", "Hcirc", "RightVectorBar", "AElig", "FilledVerySmallSquare", "ggg", "Bcy", "Poincareplane", "boxvL", "PartialD", "Icirc", "cularr", "boxh", "andv", "sung", "RightDoubleBracket", "jcirc", "UnderBar", "RightArrow", "circledcirc", "Alpha", "leftharpoonup", "cularrp", "RightArrowLeftArrow", "varsigma", "numero", "ffllig", "LowerLeftArrow", "expectation", "Ocirc", "yacy", "lambda", "NotSucceedsEqual", "boxvR", "bigtriangledown", "ang", "xuplus", "nabla", "boxvl", "Eta", "Acy", "kcy", "gcy", "LeftRightVector", "ccedil", "Backslash", "hslash", "Pcy", "Gcy", "gtquest", "Lambda", "odiv", "leftharpoondown", "longmapsto", "Jukcy", "ldrdhar", "xutri", "nRightarrow", "ExponentialE", "nrightarrow", "Acirc", "NoBreak", "gcirc", "ange", "curarrm", "SHCHcy", "yuml", "subnE", "DDotrahd", "RuleDelayed", "Gcirc", "Jsercy", "gtcc", "iukcy", "updownarrow", "curlyvee", "ffilig", "yicy", "divonx", "gtrapprox", "subdot", "leftrightarrows", "auml", "Updownarrow", "rightleftarrows", "DownRightVector", "DownRightVectorBar", "hcirc", "Rrightarrow", "longrightarrow", "cupdot", "ac", "hookrightarrow", "NegativeThickSpace", "subE", "twoheadrightarrow", "downharpoonright", "downharpoonleft", "aelig", "rdldhar", "curlywedge", "hybull", "sube", "Longrightarrow", "Cedilla", "notinva", "SucceedsEqual", "leftrightarrow", "straightepsilon", "amalg", "atilde", "RightCeiling", "Leftrightarrow", "subsim", "VerticalLine", "RightUpVector", "RightUpVectorBar", "RightDownVector", "RightDownVectorBar", "alefsym", "circlearrowright", "circlearrowleft", "Iukcy", "otimesas", "intercal", "thickapprox", "jukcy", "notniva", "precnapprox", "cuvee", "aring", "ccirc", "rightarrow", "Integral", "xcirc", "jsercy", "checkmark", "VerticalTilde", "boxvH", "NotRightTriangleBar", "NotRightTriangleEqual", "NotRightTriangle", "LeftVectorBar", "boxvh", "boxbox", "ycy", "subedot", "SOFTcy", "Rightarrow", "alpha", "shchcy", "softcy", "acy", "ycirc", "bigcirc", "ImaginaryI", "approx", "SupersetEqual", "vzigzag", "cuesc", "UnderParenthesis", "acirc", "succapprox", "mcomma", "angmsdae", "angmsdab", "angmsdaf", "angsph", "luruhar", "angmsdad", "twoheadleftarrow", "cylcty", "straightphi", "multimap", "RightArrowBar", "ldrushar", "LeftAngleBracket", "ruluhar", "curlyeqprec", "yucy", "lurdshar", "hardcy", "rightharpoondown", "rightharpoonup", "HARDcy", "SubsetEqual", "digamma", "udblac", "SuchThat", "cuwed", "Udblac", "angmsdag", "angmsdah", "VerticalBar", "VerticalSeparator", "rightarrowtail", "odblac", "succnapprox", "angmsdac", "Odblac", "cupbrcap", "angmsdaa", "curlyeqsucc", "curvearrowleft", "curvearrowright" }; #define entity_pool ((const char *) &entity_pool_contents) const struct html_ent * find_entity (register const char *str, register unsigned int len) { static const unsigned char lengthtable[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 4, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 4, 0, 0, 3, 0, 0, 0, 0, 0, 0, 6, 0, 6, 5, 0, 5, 3, 4, 3, 4, 0, 4, 0, 2, 5, 4, 0, 0, 0, 2, 0, 7, 0, 7, 3, 0, 5, 0, 0, 0, 0, 0, 4, 0, 0, 6, 0, 0, 0, 3, 6, 0, 4, 0, 0, 0, 0, 6, 4, 5, 0, 0, 0, 5, 0, 5, 0, 6, 0, 0, 0, 4, 5, 5, 5, 3, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 9, 0, 0, 0, 0, 3, 4, 0, 3, 0, 0, 5, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 5, 0, 5, 0, 5, 6, 0, 6, 5, 0, 2, 5, 0, 5, 0, 0, 0, 0, 4, 0, 0, 0, 3, 0, 3, 5, 0, 0, 5, 0, 0, 0, 6, 0, 10, 0, 4, 0, 0, 5, 3, 5, 0, 0, 0, 0, 0, 0, 0, 5, 0, 3, 0, 0, 0, 0, 6, 6, 0, 6, 0, 0, 0, 0, 6, 0, 6, 0, 2, 0, 0, 0, 4, 7, 0, 7, 0, 5, 0, 0, 0, 0, 0, 0, 0, 3, 0, 4, 0, 4, 6, 0, 3, 0, 0, 0, 0, 0, 0, 4, 4, 3, 0, 4, 0, 0, 2, 0, 0, 0, 4, 0, 4, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 2, 0, 0, 0, 5, 0, 2, 0, 0, 0, 0, 0, 0, 0, 3, 2, 4, 0, 6, 0, 0, 3, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 3, 4, 0, 0, 0, 0, 4, 6, 0, 0, 0, 5, 5, 5, 0, 13, 0, 0, 4, 0, 0, 5, 0, 4, 4, 5, 17, 18, 0, 0, 0, 0, 0, 5, 0, 0, 17, 0, 0, 0, 0, 0, 5, 5, 0, 0, 0, 5, 5, 0, 0, 0, 8, 0, 0, 0, 3, 0, 0, 6, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 5, 6, 0, 0, 0, 4, 0, 0, 5, 0, 6, 6, 6, 6, 6, 6, 6, 0, 0, 6, 0, 6, 0, 6, 6, 6, 6, 6, 6, 0, 0, 0, 6, 0, 6, 3, 4, 0, 0, 4, 3, 5, 0, 0, 3, 0, 0, 0, 11, 5, 0, 0, 0, 4, 0, 0, 6, 0, 0, 0, 5, 0, 0, 0, 5, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 5, 3, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 4, 0, 4, 0, 0, 0, 0, 0, 0, 6, 0, 0, 5, 0, 0, 0, 0, 3, 6, 0, 0, 0, 0, 0, 8, 8, 0, 0, 0, 4, 6, 0, 0, 8, 0, 8, 0, 2, 0, 0, 0, 0, 4, 0, 0, 0, 4, 0, 6, 0, 0, 0, 0, 6, 0, 4, 0, 0, 0, 0, 6, 0, 5, 6, 2, 5, 8, 5, 0, 0, 4, 0, 4, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 9, 0, 4, 4, 4, 0, 4, 6, 4, 4, 4, 0, 0, 0, 5, 4, 5, 4, 0, 0, 0, 0, 0, 4, 0, 0, 0, 4, 0, 4, 5, 4, 5, 0, 0, 4, 0, 5, 0, 0, 0, 4, 0, 0, 0, 0, 4, 4, 0, 5, 0, 0, 11, 0, 0, 6, 0, 0, 3, 0, 0, 0, 0, 6, 0, 4, 0, 0, 4, 0, 0, 0, 0, 4, 0, 0, 0, 0, 7, 4, 4, 0, 7, 0, 0, 0, 0, 0, 5, 0, 0, 0, 3, 8, 4, 0, 0, 0, 5, 0, 6, 0, 0, 0, 0, 6, 0, 4, 0, 0, 0, 5, 0, 6, 0, 0, 0, 5, 5, 0, 0, 3, 6, 2, 0, 0, 4, 0, 0, 7, 0, 4, 0, 4, 4, 4, 3, 5, 0, 0, 0, 0, 0, 0, 6, 0, 4, 4, 0, 0, 0, 12, 13, 0, 0, 6, 8, 0, 2, 0, 0, 17, 0, 0, 0, 4, 0, 5, 0, 7, 0, 5, 0, 0, 0, 5, 4, 5, 0, 0, 3, 0, 0, 0, 5, 0, 5, 12, 13, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 7, 0, 0, 6, 6, 6, 0, 4, 0, 0, 0, 0, 17, 0, 0, 4, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 3, 6, 9, 0, 0, 0, 9, 0, 0, 0, 0, 0, 6, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 19, 0, 5, 0, 0, 17, 0, 0, 14, 0, 0, 0, 0, 12, 4, 0, 0, 0, 4, 0, 2, 0, 4, 0, 6, 0, 0, 3, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 4, 4, 0, 4, 0, 4, 4, 4, 0, 0, 0, 0, 4, 0, 4, 0, 4, 9, 0, 0, 4, 2, 0, 0, 4, 2, 4, 4, 0, 0, 0, 0, 4, 6, 0, 0, 6, 9, 4, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 4, 2, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 10, 6, 0, 0, 0, 0, 6, 4, 6, 4, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 9, 0, 0, 4, 0, 0, 0, 0, 0, 7, 4, 4, 7, 0, 7, 5, 0, 0, 6, 4, 4, 4, 0, 4, 4, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 4, 0, 0, 0, 4, 0, 0, 4, 4, 6, 0, 0, 0, 3, 5, 3, 5, 11, 4, 0, 0, 4, 0, 0, 0, 5, 0, 0, 0, 0, 7, 0, 0, 0, 0, 5, 0, 5, 0, 0, 0, 3, 5, 4, 0, 0, 0, 5, 0, 6, 9, 7, 2, 0, 4, 0, 0, 4, 0, 0, 0, 0, 4, 5, 6, 0, 0, 0, 0, 9, 10, 0, 0, 0, 5, 0, 0, 0, 0, 11, 0, 0, 6, 0, 0, 0, 0, 0, 0, 4, 8, 6, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 5, 6, 0, 0, 0, 13, 5, 5, 6, 0, 0, 0, 0, 2, 0, 0, 0, 4, 2, 4, 0, 0, 6, 4, 0, 4, 0, 0, 0, 4, 0, 21, 0, 0, 0, 6, 0, 3, 0, 0, 0, 6, 6, 0, 3, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 4, 0, 6, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 7, 3, 0, 0, 0, 0, 0, 0, 0, 7, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 3, 3, 0, 3, 15, 3, 3, 3, 0, 0, 0, 3, 3, 6, 3, 6, 0, 0, 0, 0, 3, 0, 0, 4, 3, 0, 3, 0, 12, 0, 0, 0, 3, 0, 4, 0, 0, 0, 3, 0, 12, 0, 4, 5, 0, 9, 0, 0, 7, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 5, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 4, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 12, 0, 0, 0, 0, 0, 5, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 5, 0, 3, 3, 0, 0, 6, 0, 0, 0, 0, 0, 4, 0, 0, 3, 3, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 3, 7, 0, 0, 8, 0, 0, 0, 0, 0, 0, 3, 4, 0, 6, 0, 0, 0, 15, 0, 0, 0, 0, 0, 0, 0, 9, 0, 0, 0, 2, 0, 0, 0, 0, 9, 3, 0, 0, 0, 0, 0, 0, 6, 0, 0, 7, 3, 24, 0, 0, 0, 0, 5, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 7, 4, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 3, 3, 0, 4, 0, 7, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 5, 2, 0, 0, 0, 6, 0, 3, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 9, 5, 7, 0, 0, 0, 0, 0, 0, 0, 0, 7, 15, 7, 8, 4, 0, 5, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 4, 4, 5, 0, 0, 0, 0, 6, 14, 3, 15, 0, 6, 0, 0, 0, 3, 0, 3, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 6, 0, 0, 0, 0, 0, 0, 5, 0, 0, 5, 16, 0, 5, 10, 0, 0, 0, 5, 7, 0, 5, 0, 0, 6, 0, 3, 0, 0, 11, 5, 0, 0, 4, 5, 0, 0, 5, 0, 0, 3, 0, 0, 0, 0, 8, 0, 0, 0, 5, 0, 0, 0, 6, 3, 0, 0, 0, 0, 0, 5, 0, 0, 3, 3, 3, 0, 0, 0, 6, 0, 0, 5, 6, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 11, 0, 6, 0, 6, 0, 0, 13, 0, 0, 7, 0, 0, 0, 0, 7, 0, 6, 4, 5, 0, 3, 0, 0, 5, 3, 0, 0, 0, 0, 0, 6, 0, 0, 4, 0, 0, 0, 0, 3, 6, 5, 0, 0, 0, 0, 11, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 11, 0, 5, 5, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 8, 0, 7, 4, 0, 0, 0, 0, 5, 4, 9, 0, 0, 5, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 9, 0, 6, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 6, 0, 4, 0, 0, 14, 5, 0, 0, 8, 0, 0, 0, 20, 7, 0, 0, 0, 0, 0, 0, 0, 0, 5, 3, 0, 0, 4, 6, 0, 0, 0, 0, 6, 0, 0, 0, 7, 0, 3, 6, 4, 6, 0, 0, 0, 0, 0, 0, 6, 3, 4, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 11, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 4, 0, 0, 0, 0, 0, 0, 0, 13, 18, 5, 0, 3, 0, 7, 0, 4, 0, 0, 0, 4, 0, 0, 10, 11, 0, 0, 0, 6, 0, 6, 0, 0, 5, 0, 5, 12, 12, 0, 0, 0, 4, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 14, 0, 0, 0, 2, 4, 8, 4, 0, 3, 0, 0, 7, 0, 3, 0, 0, 0, 3, 2, 0, 0, 0, 0, 6, 0, 6, 4, 6, 7, 6, 6, 6, 0, 10, 0, 0, 0, 3, 6, 0, 4, 0, 0, 0, 0, 0, 4, 0, 6, 6, 0, 4, 0, 0, 0, 7, 0, 0, 7, 0, 0, 4, 0, 4, 0, 5, 6, 0, 6, 0, 3, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 9, 0, 0, 0, 0, 0, 8, 14, 0, 3, 0, 0, 0, 0, 0, 0, 8, 0, 0, 7, 5, 0, 0, 0, 4, 0, 0, 0, 17, 7, 0, 0, 4, 0, 0, 7, 0, 5, 0, 0, 7, 5, 0, 0, 4, 0, 7, 2, 20, 0, 0, 0, 0, 13, 0, 0, 0, 0, 6, 0, 7, 3, 5, 4, 0, 0, 0, 0, 5, 5, 0, 0, 0, 0, 0, 4, 5, 0, 0, 0, 0, 0, 0, 0, 5, 0, 5, 0, 0, 6, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 4, 9, 0, 5, 12, 0, 0, 0, 0, 5, 0, 5, 4, 0, 0, 0, 9, 0, 0, 0, 10, 10, 0, 0, 4, 6, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 6, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 6, 6, 0, 3, 0, 0, 0, 7, 0, 0, 0, 0, 7, 4, 0, 0, 0, 0, 0, 4, 0, 9, 0, 0, 3, 0, 0, 0, 7, 0, 4, 0, 0, 5, 6, 0, 0, 6, 3, 5, 4, 0, 0, 0, 0, 0, 6, 0, 5, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 5, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 6, 0, 0, 6, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 6, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 6, 0, 6, 0, 0, 6, 0, 0, 18, 0, 6, 0, 20, 15, 0, 0, 4, 4, 0, 0, 0, 6, 0, 0, 0, 3, 0, 0, 0, 0, 0, 5, 4, 4, 0, 7, 0, 6, 0, 4, 0, 5, 0, 0, 0, 0, 5, 0, 0, 0, 4, 4, 0, 0, 0, 0, 4, 0, 4, 0, 11, 0, 20, 23, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 8, 0, 0, 0, 6, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 4, 0, 0, 3, 0, 0, 6, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 13, 0, 0, 9, 0, 0, 0, 5, 0, 0, 0, 5, 0, 3, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 3, 0, 0, 17, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 9, 0, 0, 0, 6, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 7, 0, 0, 0, 9, 0, 0, 0, 0, 0, 0, 14, 0, 0, 11, 0, 6, 0, 6, 0, 7, 5, 0, 0, 0, 6, 12, 12, 0, 0, 0, 0, 16, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 5, 0, 0, 0, 7, 0, 0, 5, 0, 0, 0, 0, 0, 0, 6, 0, 14, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 5, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 5, 0, 0, 0, 0, 0, 0, 5, 0, 5, 0, 0, 0, 0, 0, 11, 6, 6, 3, 0, 0, 0, 0, 7, 0, 6, 0, 6, 6, 4, 0, 0, 0, 7, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 5, 0, 0, 0, 6, 0, 0, 0, 0, 4, 4, 0, 0, 0, 0, 3, 3, 6, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 6, 0, 0, 0, 4, 6, 0, 4, 4, 0, 0, 0, 0, 13, 0, 4, 0, 0, 0, 0, 4, 2, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 10, 0, 9, 0, 0, 4, 6, 0, 5, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 8, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 12, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 12, 0, 0, 0, 0, 0, 0, 0, 18, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 7, 0, 0, 0, 0, 5, 0, 5, 0, 0, 0, 6, 0, 0, 5, 0, 0, 6, 0, 6, 0, 0, 13, 6, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 6, 0, 6, 7, 0, 0, 0, 0, 0, 0, 0, 14, 0, 6, 15, 0, 0, 7, 0, 3, 0, 3, 0, 0, 0, 9, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 12, 0, 0, 15, 0, 0, 0, 6, 0, 0, 6, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 7, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 9, 4, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 2, 15, 0, 0, 0, 5, 0, 5, 0, 4, 0, 0, 0, 0, 0, 0, 16, 0, 3, 3, 10, 0, 0, 0, 0, 0, 0, 0, 0, 4, 5, 4, 5, 4, 0, 0, 6, 0, 5, 4, 0, 5, 5, 3, 5, 0, 4, 0, 6, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 3, 0, 0, 0, 0, 0, 3, 0, 0, 6, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 8, 6, 0, 0, 0, 0, 0, 0, 0, 5, 16, 0, 5, 7, 0, 6, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 7, 0, 0, 5, 0, 0, 0, 0, 6, 0, 5, 4, 5, 0, 5, 5, 0, 0, 0, 0, 5, 2, 6, 4, 0, 5, 0, 0, 5, 0, 4, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 9, 0, 0, 0, 0, 6, 0, 0, 0, 0, 3, 5, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 6, 5, 0, 0, 4, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 4, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 4, 2, 6, 0, 6, 3, 3, 0, 0, 3, 0, 4, 0, 6, 0, 3, 0, 0, 6, 0, 5, 31, 0, 0, 0, 0, 0, 0, 0, 3, 6, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 5, 0, 0, 0, 3, 0, 0, 0, 0, 6, 0, 8, 0, 5, 4, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 5, 0, 0, 5, 0, 0, 0, 19, 0, 0, 0, 0, 24, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 9, 0, 0, 0, 5, 0, 0, 0, 6, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 16, 5, 0, 0, 3, 4, 4, 0, 5, 4, 5, 0, 0, 0, 13, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 5, 0, 0, 0, 0, 0, 0, 6, 0, 3, 0, 7, 0, 10, 0, 0, 0, 0, 6, 0, 6, 0, 0, 13, 0, 0, 0, 5, 0, 8, 0, 6, 0, 6, 8, 6, 0, 0, 6, 6, 0, 10, 0, 8, 6, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 11, 0, 0, 0, 6, 0, 0, 0, 0, 7, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 17, 6, 0, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 4, 0, 4, 0, 0, 0, 0, 0, 7, 0, 14, 7, 6, 0, 6, 0, 7, 0, 0, 0, 0, 0, 0, 0, 4, 0, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 10, 4, 14, 0, 0, 0, 9, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 4, 0, 6, 0, 0, 0, 0, 0, 0, 0, 6, 3, 8, 4, 6, 6, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 6, 0, 4, 0, 2, 0, 20, 21, 0, 0, 2, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 14, 4, 6, 17, 0, 0, 0, 0, 0, 0, 0, 0, 6, 6, 0, 0, 0, 5, 0, 0, 4, 6, 0, 2, 7, 0, 6, 5, 0, 8, 0, 0, 5, 0, 4, 0, 0, 0, 5, 0, 4, 15, 5, 0, 4, 6, 0, 0, 0, 0, 5, 5, 0, 0, 0, 0, 0, 0, 0, 17, 5, 0, 0, 0, 9, 6, 0, 0, 12, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 7, 5, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 12, 0, 0, 0, 6, 0, 0, 0, 0, 10, 3, 0, 0, 0, 4, 0, 5, 0, 0, 0, 0, 0, 4, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 9, 0, 6, 0, 6, 0, 0, 0, 0, 19, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 5, 0, 0, 5, 0, 6, 3, 6, 0, 0, 0, 0, 0, 0, 0, 4, 0, 4, 2, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 6, 0, 6, 0, 6, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 17, 0, 0, 7, 0, 0, 2, 6, 2, 0, 0, 0, 2, 0, 0, 0, 0, 3, 8, 0, 0, 3, 0, 5, 0, 5, 6, 0, 0, 0, 0, 18, 0, 0, 0, 0, 5, 0, 7, 0, 0, 9, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 4, 0, 0, 4, 0, 9, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 5, 0, 4, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 5, 0, 5, 6, 0, 0, 0, 3, 3, 5, 0, 0, 0, 0, 6, 0, 0, 0, 6, 0, 9, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 4, 6, 13, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 8, 6, 8, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 12, 0, 6, 0, 0, 0, 6, 0, 0, 0, 6, 4, 0, 0, 7, 6, 5, 0, 0, 6, 0, 5, 5, 5, 0, 0, 0, 9, 0, 0, 0, 0, 0, 5, 0, 6, 8, 0, 0, 6, 0, 5, 8, 0, 0, 0, 6, 0, 4, 0, 9, 0, 0, 0, 0, 4, 6, 4, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 4, 11, 0, 0, 8, 9, 0, 0, 0, 0, 3, 5, 3, 0, 0, 0, 0, 6, 4, 0, 0, 0, 9, 4, 3, 0, 2, 0, 0, 0, 0, 0, 7, 5, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 14, 3, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 3, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 10, 7, 5, 0, 6, 0, 6, 0, 3, 17, 0, 0, 0, 0, 0, 0, 20, 0, 14, 4, 0, 0, 0, 0, 0, 0, 19, 6, 6, 0, 10, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 6, 0, 0, 3, 0, 0, 0, 4, 5, 0, 0, 4, 0, 5, 0, 0, 0, 0, 0, 0, 7, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 3, 0, 0, 0, 0, 0, 0, 7, 0, 3, 0, 4, 0, 3, 0, 4, 0, 0, 13, 0, 4, 0, 0, 0, 0, 0, 0, 0, 12, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 6, 0, 0, 0, 0, 0, 7, 0, 13, 0, 0, 15, 0, 0, 5, 9, 0, 0, 0, 6, 0, 6, 0, 0, 4, 6, 0, 0, 6, 4, 4, 0, 16, 0, 4, 0, 3, 0, 0, 11, 5, 15, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 5, 0, 5, 4, 0, 0, 4, 0, 20, 4, 0, 0, 0, 0, 0, 5, 15, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 5, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 5, 5, 0, 22, 0, 0, 7, 8, 0, 4, 0, 17, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 6, 7, 0, 0, 0, 0, 6, 0, 6, 0, 0, 0, 6, 0, 0, 0, 0, 0, 4, 0, 5, 0, 12, 15, 6, 0, 13, 0, 4, 0, 5, 4, 6, 0, 0, 0, 0, 4, 0, 0, 4, 3, 5, 0, 0, 0, 0, 0, 0, 4, 0, 4, 0, 0, 0, 0, 0, 0, 4, 0, 0, 9, 0, 0, 20, 0, 4, 10, 0, 0, 0, 0, 4, 0, 5, 0, 0, 8, 6, 0, 5, 4, 0, 0, 3, 0, 4, 0, 0, 6, 6, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 9, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 17, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 5, 6, 0, 5, 0, 0, 0, 0, 0, 0, 5, 0, 8, 0, 0, 0, 4, 0, 0, 0, 0, 0, 16, 15, 4, 0, 0, 11, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 2, 0, 5, 0, 10, 0, 0, 5, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 5, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 4, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 6, 5, 4, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 6, 0, 0, 0, 0, 2, 4, 5, 0, 0, 0, 8, 0, 0, 3, 0, 8, 0, 0, 4, 18, 0, 0, 0, 0, 4, 5, 0, 0, 0, 16, 0, 0, 0, 0, 7, 0, 2, 3, 5, 0, 0, 5, 0, 4, 4, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 14, 0, 0, 0, 0, 5, 0, 0, 6, 0, 6, 0, 5, 0, 5, 0, 5, 15, 0, 0, 8, 17, 12, 0, 0, 0, 0, 0, 6, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 5, 0, 0, 20, 0, 0, 0, 0, 0, 11, 0, 5, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 6, 0, 6, 0, 6, 0, 6, 0, 5, 8, 0, 0, 0, 0, 0, 6, 14, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 5, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 8, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 19, 0, 0, 0, 0, 0, 0, 7, 0, 0, 16, 0, 14, 0, 18, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 5, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 14, 0, 0, 17, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 5, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 8, 17, 0, 0, 0, 5, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 9, 0, 15, 0, 5, 0, 5, 0, 0, 0, 0, 0, 0, 6, 5, 0, 0, 0, 0, 6, 4, 0, 0, 9, 0, 0, 0, 0, 0, 6, 0, 6, 0, 0, 8, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 6, 2, 0, 0, 6, 0, 12, 6, 0, 0, 0, 16, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 14, 22, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 8, 0, 5, 0, 0, 6, 0, 0, 0, 6, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 5, 6, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 14, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 5, 0, 9, 0, 0, 0, 5, 0, 0, 0, 0, 4, 6, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 9, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 21, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 6, 0, 0, 0, 0, 0, 3, 5, 0, 0, 5, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 2, 0, 9, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 5, 0, 0, 0, 0, 0, 0, 0, 0, 8, 5, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 5, 6, 0, 0, 4, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 9, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 12, 0, 0, 0, 18, 10, 0, 0, 18, 0, 7, 0, 0, 0, 6, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 5, 0, 0, 0, 0, 6, 0, 0, 5, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 4, 0, 0, 0, 5, 0, 12, 4, 12, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 5, 0, 5, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 4, 0, 0, 0, 0, 7, 5, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 4, 5, 0, 0, 0, 5, 6, 7, 7, 0, 0, 0, 0, 0, 0, 0, 6, 0, 8, 0, 0, 0, 0, 5, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 16, 0, 0, 0, 0, 0, 0, 17, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 4, 6, 0, 0, 0, 5, 0, 0, 0, 8, 0, 0, 0, 0, 0, 17, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 17, 0, 5, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 18, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 8, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 15, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 9, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 4, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 8, 4, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 4, 6, 8, 0, 5, 0, 0, 4, 4, 0, 5, 4, 5, 0, 0, 0, 0, 0, 0, 6, 0, 0, 5, 0, 0, 18, 0, 5, 0, 0, 0, 19, 0, 0, 8, 0, 14, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 5, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 5, 13, 0, 0, 0, 7, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 3, 0, 0, 4, 0, 6, 13, 0, 8, 0, 5, 0, 0, 0, 5, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 3, 0, 3, 0, 3, 0, 3, 3, 3, 4, 0, 4, 0, 3, 5, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 3, 4, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 5, 0, 18, 0, 0, 15, 7, 0, 3, 0, 0, 6, 5, 0, 5, 0, 3, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 12, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 3, 3, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 3, 3, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 7, 10, 0, 0, 0, 0, 0, 4, 0, 0, 9, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 4, 0, 0, 0, 0, 0, 0, 0, 5, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 12, 0, 0, 0, 5, 6, 0, 0, 0, 0, 0, 5, 0, 0, 0, 5, 0, 0, 0, 0, 5, 0, 17, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 6, 5, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 4, 15, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 9, 6, 0, 0, 0, 3, 0, 0, 0, 0, 0, 7, 0, 0, 20, 0, 5, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 5, 0, 0, 0, 3, 0, 0, 6, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 9, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 5, 6, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 5, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 3, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 8, 0, 0, 5, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 6, 8, 0, 0, 17, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 17, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 7, 0, 0, 3, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 7, 5, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 4, 4, 4, 0, 0, 0, 0, 6, 11, 19, 0, 0, 5, 17, 0, 0, 0, 0, 0, 16, 5, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 7, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 7, 8, 0, 0, 0, 0, 0, 13, 0, 16, 5, 4, 0, 0, 0, 6, 0, 0, 5, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 21, 9, 6, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 8, 9, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 9, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 7, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 6, 0, 0, 0, 0, 0, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 4, 10, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 10, 0, 10, 0, 0, 0, 21, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 5, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 12, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 20, 0, 3, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 3, 0, 0, 0, 0, 5, 14, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 21, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 5, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 4, 0, 4, 0, 0, 0, 18, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 11, 5, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 7, 0, 19, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 16, 5, 0, 15, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 15, 0, 0, 0, 0, 0, 6, 0, 0, 0, 9, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 12, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 4, 7, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 4, 0, 0, 0, 5, 0, 0, 8, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 9, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 15, 0, 0, 0, 0, 0, 4, 0, 0, 11, 0, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 15, 0, 0, 18, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 18, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 17, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 15, 0, 0, 0, 0, 5, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 12, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 12, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 15, 0, 0, 18, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 15, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 5, 0, 0, 0, 7, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 9, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 19, 0, 0, 0, 21, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 16, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 17, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 15 }; static const struct html_ent wordlist[] = { {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1501 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str39), {226, 134, 146, 0}}, {-1,{0}}, #line 833 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str41), {226, 134, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 844 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str49), {226, 170, 171, 0}}, {-1,{0}}, {-1,{0}}, #line 1903 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str52), {226, 134, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 1235 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str55), {226, 138, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1510 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str62), {226, 134, 163, 0}}, {-1,{0}}, #line 841 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str64), {226, 134, 162, 0}}, #line 1601 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str65), {226, 135, 190, 0}}, {-1,{0}}, #line 963 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str67), {226, 135, 189, 0}}, #line 1168 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str68), {194, 172, 0}}, #line 1609 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str69), {41, 0}}, #line 146 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str70), {226, 138, 165, 0}}, #line 989 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str71), {40, 0}}, {-1,{0}}, #line 1715 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str73), {226, 136, 165, 0}}, {-1,{0}}, #line 945 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str75), {226, 137, 170, 0}}, #line 1926 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str76), {226, 134, 190, 0}}, #line 505 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str77), {226, 139, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 482 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str81), {226, 170, 153, 0}}, {-1,{0}}, #line 1607 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str83), {226, 168, 181, 0}}, {-1,{0}}, #line 981 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str85), {226, 168, 180, 0}}, #line 1388 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str86), {226, 136, 165, 0}}, {-1,{0}}, #line 1132 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str88), {226, 134, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1231 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str94), {226, 136, 166, 0}}, {-1,{0}}, {-1,{0}}, #line 1872 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str97), {226, 128, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 486 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str101), {226, 170, 149, 0}}, #line 506 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str102), {226, 167, 163, 0}}, {-1,{0}}, #line 500 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str104), {226, 128, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 193 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str109), {226, 128, 181, 0}}, #line 955 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str110), {226, 170, 137, 0}}, #line 137 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str111), {226, 150, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 136 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str115), {226, 150, 146, 0}}, {-1,{0}}, #line 138 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str117), {226, 150, 147, 0}}, {-1,{0}}, #line 1232 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str119), {226, 171, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1143 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str123), {226, 128, 165, 0}}, #line 1594 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str124), {226, 135, 132, 0}}, #line 1233 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str125), {226, 136, 130, 0}}, #line 944 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str126), {226, 135, 135, 0}}, #line 1158 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str127), {226, 137, 174, 0}}, #line 1696 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str128), {226, 134, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1230 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str138), {226, 136, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1825 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str143), {206, 164, 0}}, #line 1991 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str144), {226, 134, 149, 0}}, {-1,{0}}, #line 1738 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str146), {226, 150, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 1141 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str149), {226, 134, 154, 0}}, {-1,{0}}, {-1,{0}}, #line 1826 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str152), {207, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 957 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str165), {226, 170, 135, 0}}, #line 1612 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str166), {226, 135, 137, 0}}, {-1,{0}}, #line 991 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str168), {226, 135, 134, 0}}, {-1,{0}}, #line 1740 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str170), {226, 134, 146, 0}}, #line 1556 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str171), {226, 165, 172, 0}}, {-1,{0}}, #line 940 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str173), {226, 165, 170, 0}}, #line 525 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str174), {226, 165, 177, 0}}, {-1,{0}}, #line 1433 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str176), {226, 137, 186, 0}}, #line 1555 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str177), {226, 135, 128, 0}}, {-1,{0}}, #line 939 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str179), {226, 134, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1904 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str184), {226, 134, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1128 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str188), {226, 137, 171, 0}}, {-1,{0}}, #line 140 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str190), {61, 0}}, #line 1241 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str191), {226, 134, 155, 0}}, {-1,{0}}, {-1,{0}}, #line 1818 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str194), {226, 134, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1497 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str198), {226, 165, 181, 0}}, {-1,{0}}, #line 1966 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str200), {226, 135, 136, 0}}, {-1,{0}}, #line 344 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str202), {226, 134, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 1516 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str205), {226, 164, 141, 0}}, #line 397 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str206), {194, 168, 0}}, #line 847 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str207), {226, 164, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1306 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str215), {226, 134, 150, 0}}, {-1,{0}}, #line 1703 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str217), {226, 170, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 496 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str222), {226, 128, 133, 0}}, #line 1507 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str223), {226, 165, 133, 0}}, {-1,{0}}, #line 839 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str225), {226, 164, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1405 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str230), {226, 132, 179, 0}}, {-1,{0}}, #line 495 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str232), {226, 128, 132, 0}}, {-1,{0}}, #line 1013 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str234), {60, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 834 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str238), {226, 134, 158, 0}}, #line 1524 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str239), {226, 166, 144, 0}}, {-1,{0}}, #line 854 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str241), {226, 166, 141, 0}}, {-1,{0}}, #line 1081 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str243), {197, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1145 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str251), {226, 137, 176, 0}}, {-1,{0}}, #line 1553 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str253), {226, 165, 164, 0}}, {-1,{0}}, #line 937 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str255), {226, 165, 162, 0}}, #line 1476 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str256), {226, 129, 151, 0}}, {-1,{0}}, #line 828 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str258), {226, 170, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1086 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str265), {194, 160, 0}}, #line 1924 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str266), {226, 165, 163, 0}}, #line 1867 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str267), {226, 138, 164, 0}}, {-1,{0}}, #line 2003 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str269), {226, 171, 171, 0}}, {-1,{0}}, {-1,{0}}, #line 946 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str272), {226, 139, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1431 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str276), {226, 170, 183, 0}}, {-1,{0}}, #line 497 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str278), {226, 128, 131, 0}}, {-1,{0}}, {-1,{0}}, #line 1078 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str281), {226, 137, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 975 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str294), {226, 134, 171, 0}}, {-1,{0}}, #line 869 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str296), {226, 137, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1669 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str300), {226, 153, 175, 0}}, {-1,{0}}, #line 473 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str302), {226, 133, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 913 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str310), {226, 169, 189, 0}}, #line 744 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str311), {226, 136, 136, 0}}, #line 1460 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str312), {226, 136, 157, 0}}, {-1,{0}}, #line 1865 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str314), {226, 140, 182, 0}}, {-1,{0}}, {-1,{0}}, #line 749 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str317), {226, 136, 171, 0}}, {-1,{0}}, #line 1104 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str319), {226, 137, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1236 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str329), {226, 139, 160, 0}}, {-1,{0}}, #line 1446 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str331), {226, 170, 175, 0}}, #line 508 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str332), {206, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1959 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str337), {207, 133, 0}}, #line 1838 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str338), {226, 136, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1522 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str342), {226, 166, 140, 0}}, #line 1657 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str343), {226, 134, 152, 0}}, #line 852 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str344), {226, 166, 139, 0}}, {-1,{0}}, #line 131 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str346), {226, 150, 180, 0}}, {-1,{0}}, {-1,{0}}, #line 959 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str349), {226, 170, 135, 0}}, {-1,{0}}, {-1,{0}}, #line 960 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str352), {226, 137, 168, 0}}, {-1,{0}}, #line 1417 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str354), {43, 0}}, #line 1153 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str355), {226, 169, 189, 0}}, #line 1105 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str356), {226, 137, 144, 0}}, #line 133 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str357), {226, 151, 130, 0}}, #line 134 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str358), {226, 150, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1101 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str364), {226, 134, 151, 0}}, {-1,{0}}, {-1,{0}}, #line 132 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str367), {226, 150, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1154 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str373), {226, 137, 174, 0}}, #line 489 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str374), {196, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2033 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str378), {226, 136, 157, 0}}, #line 1933 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str379), {197, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1700 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str383), {226, 167, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1032 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str387), {226, 164, 133, 0}}, {-1,{0}}, {-1,{0}}, #line 1419 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str390), {226, 168, 165, 0}}, #line 1167 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str391), {226, 171, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2018 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str408), {226, 128, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1398 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str426), {226, 138, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 560 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str430), {226, 150, 177, 0}}, #line 1422 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str431), {194, 177, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1150 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str435), {226, 137, 176, 0}}, {-1,{0}}, {-1,{0}}, #line 1151 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str438), {226, 137, 166, 0}}, {-1,{0}}, #line 578 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str440), {194, 190, 0}}, #line 572 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str441), {194, 188, 0}}, #line 2017 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str442), {124, 0}}, #line 570 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str443), {194, 189, 0}}, #line 579 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str444), {226, 133, 151, 0}}, #line 573 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str445), {226, 133, 149, 0}}, #line 581 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str446), {226, 133, 152, 0}}, {-1,{0}}, {-1,{0}}, #line 577 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str449), {226, 133, 150, 0}}, {-1,{0}}, #line 571 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str451), {226, 133, 147, 0}}, {-1,{0}}, #line 574 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str453), {226, 133, 153, 0}}, #line 1465 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str454), {226, 138, 176, 0}}, #line 576 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str455), {226, 133, 148, 0}}, #line 580 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str456), {226, 133, 156, 0}}, #line 575 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str457), {226, 133, 155, 0}}, #line 582 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str458), {226, 133, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 583 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str462), {226, 133, 157, 0}}, {-1,{0}}, #line 584 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str464), {226, 133, 158, 0}}, #line 909 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str465), {226, 137, 164, 0}}, #line 343 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str466), {226, 134, 147, 0}}, {-1,{0}}, {-1,{0}}, #line 1960 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str469), {207, 146, 0}}, #line 398 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str470), {203, 153, 0}}, #line 1406 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str471), {226, 152, 142, 0}}, {-1,{0}}, {-1,{0}}, #line 218 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str474), {226, 139, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 130 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str478), {226, 150, 170, 0}}, #line 1599 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str479), {226, 171, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 910 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str483), {226, 137, 166, 0}}, {-1,{0}}, {-1,{0}}, #line 748 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str486), {226, 138, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 371 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str490), {226, 135, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1554 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str494), {226, 135, 129, 0}}, {-1,{0}}, #line 938 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str496), {226, 134, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1420 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str505), {226, 169, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1932 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str511), {197, 170, 0}}, #line 2014 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str512), {226, 139, 129, 0}}, {-1,{0}}, {-1,{0}}, #line 1502 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str515), {226, 134, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 303 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str527), {226, 168, 175, 0}}, {-1,{0}}, #line 1619 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str529), {93, 0}}, {-1,{0}}, #line 1005 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str531), {91, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1509 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str538), {226, 164, 150, 0}}, {-1,{0}}, {-1,{0}}, #line 529 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str541), {226, 137, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2013 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str546), {226, 136, 168, 0}}, #line 1088 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str547), {226, 137, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 947 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str553), {226, 140, 158, 0}}, #line 569 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str554), {226, 168, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1739 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str558), {226, 150, 170, 0}}, #line 1413 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str559), {226, 132, 143, 0}}, {-1,{0}}, {-1,{0}}, #line 524 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str562), {226, 167, 165, 0}}, {-1,{0}}, #line 1929 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str564), {226, 140, 156, 0}}, {-1,{0}}, #line 2054 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str566), {226, 132, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 988 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str571), {226, 167, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 298 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str575), {194, 169, 0}}, {-1,{0}}, #line 1928 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str577), {226, 140, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2012 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str582), {226, 138, 187, 0}}, {-1,{0}}, #line 1391 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str584), {226, 136, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1729 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str589), {226, 150, 161, 0}}, {-1,{0}}, #line 1087 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str591), {226, 137, 142, 0}}, #line 107 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str592), {226, 132, 172, 0}}, #line 2055 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str593), {226, 137, 128, 0}}, #line 1517 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str594), {226, 164, 143, 0}}, #line 992 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str595), {226, 140, 159, 0}}, #line 848 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str596), {226, 164, 142, 0}}, {-1,{0}}, {-1,{0}}, #line 143 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str599), {226, 140, 144, 0}}, {-1,{0}}, #line 1661 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str601), {59, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1968 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str606), {226, 140, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1217 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str612), {226, 138, 130, 0}}, {-1,{0}}, #line 1604 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str614), {240, 157, 149, 163}}, #line 1475 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str615), {226, 132, 154, 0}}, #line 979 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str616), {240, 157, 149, 157}}, {-1,{0}}, #line 1712 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str618), {240, 157, 149, 164}}, #line 1967 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str619), {226, 140, 157, 0}}, #line 1868 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str620), {240, 157, 149, 139}}, #line 2126 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str621), {226, 132, 164, 0}}, #line 504 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str622), {240, 157, 149, 150}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1603 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str626), {226, 166, 134, 0}}, #line 1944 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str627), {240, 157, 149, 166}}, #line 977 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str628), {226, 166, 133, 0}}, #line 1869 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str629), {240, 157, 149, 165}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2074 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str635), {240, 157, 149, 143}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1165 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str639), {240, 157, 149, 159}}, {-1,{0}}, #line 145 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str641), {240, 157, 149, 147}}, #line 511 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str642), {207, 181, 0}}, #line 561 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str643), {198, 146, 0}}, #line 733 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str644), {196, 171, 0}}, {-1,{0}}, {-1,{0}}, #line 791 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str647), {240, 157, 149, 129}}, {-1,{0}}, #line 1134 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str649), {226, 171, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2052 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str653), {240, 157, 149, 142}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1720 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str658), {226, 136, 154, 0}}, #line 1262 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str659), {226, 138, 132, 0}}, {-1,{0}}, #line 1080 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str661), {226, 137, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 1223 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str664), {226, 138, 131, 0}}, {-1,{0}}, {-1,{0}}, #line 196 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str667), {194, 166, 0}}, {-1,{0}}, {-1,{0}}, #line 1710 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str670), {47, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 460 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str675), {226, 169, 174, 0}}, {-1,{0}}, #line 1428 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str677), {240, 157, 149, 161}}, {-1,{0}}, {-1,{0}}, #line 369 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str680), {226, 165, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2031 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str685), {240, 157, 149, 141}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1273 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str690), {226, 138, 131, 0}}, #line 1270 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str691), {226, 138, 133, 0}}, #line 2002 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str692), {226, 171, 168, 0}}, {-1,{0}}, #line 1265 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str694), {226, 138, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1850 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str700), {226, 137, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1136 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str704), {226, 139, 188, 0}}, #line 1459 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str705), {226, 140, 147, 0}}, #line 1709 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str706), {226, 167, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 961 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str710), {226, 139, 166, 0}}, {-1,{0}}, #line 1708 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str712), {226, 140, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1730 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str717), {226, 150, 161, 0}}, {-1,{0}}, #line 2032 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str719), {240, 157, 149, 167}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1925 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str723), {226, 134, 191, 0}}, {-1,{0}}, #line 1930 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str725), {226, 140, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 514 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str729), {226, 137, 130, 0}}, #line 522 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str730), {226, 137, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 485 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str733), {226, 132, 147, 0}}, #line 1699 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str734), {226, 168, 179, 0}}, #line 1066 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str735), {226, 136, 147, 0}}, {-1,{0}}, {-1,{0}}, #line 813 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str738), {240, 157, 149, 130}}, {-1,{0}}, {-1,{0}}, #line 1695 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str741), {226, 165, 178, 0}}, {-1,{0}}, #line 558 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str743), {226, 153, 173, 0}}, {-1,{0}}, #line 1064 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str745), {240, 157, 149, 132}}, #line 1711 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str746), {240, 157, 149, 138}}, #line 1061 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str747), {226, 128, 166, 0}}, #line 1596 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str748), {226, 128, 143, 0}}, #line 767 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str749), {226, 168, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 990 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str756), {226, 166, 147, 0}}, {-1,{0}}, #line 563 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str758), {240, 157, 149, 151}}, #line 1943 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str759), {240, 157, 149, 140}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1995 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str763), {226, 138, 138, 0}}, #line 1996 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str764), {226, 171, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 1969 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str767), {226, 140, 142, 0}}, #line 927 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str768), {226, 170, 161, 0}}, {-1,{0}}, #line 1542 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str770), {226, 132, 156, 0}}, {-1,{0}}, {-1,{0}}, #line 1201 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str773), {226, 170, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 395 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str777), {240, 157, 148, 187}}, {-1,{0}}, #line 567 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str779), {226, 171, 153, 0}}, {-1,{0}}, #line 1260 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str781), {226, 139, 162, 0}}, {-1,{0}}, #line 1272 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str783), {226, 138, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1264 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str787), {226, 138, 136, 0}}, #line 1474 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str788), {240, 157, 149, 162}}, #line 1595 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str789), {226, 135, 140, 0}}, {-1,{0}}, {-1,{0}}, #line 995 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str792), {226, 128, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1156 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str796), {226, 137, 180, 0}}, {-1,{0}}, #line 1430 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str798), {194, 163, 0}}, #line 1997 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str799), {226, 138, 139, 0}}, #line 1998 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str800), {226, 171, 140, 0}}, {-1,{0}}, #line 141 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str802), {226, 137, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 978 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str813), {240, 157, 149, 131}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1261 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str817), {226, 139, 163, 0}}, {-1,{0}}, {-1,{0}}, #line 1506 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str820), {226, 134, 172, 0}}, #line 2045 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str821), {226, 169, 159, 0}}, #line 838 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str822), {226, 134, 171, 0}}, {-1,{0}}, #line 2100 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str824), {240, 157, 149, 144}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1209 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str829), {226, 136, 140, 0}}, {-1,{0}}, {-1,{0}}, #line 294 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str832), {226, 132, 130, 0}}, #line 993 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str833), {226, 135, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1390 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str848), {226, 171, 189, 0}}, #line 1934 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str849), {194, 168, 0}}, #line 1038 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str850), {226, 150, 174, 0}}, #line 1274 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str851), {226, 138, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1266 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str855), {226, 138, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1737 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str861), {226, 150, 170, 0}}, #line 2020 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str862), {226, 128, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1735 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str874), {226, 138, 146, 0}}, {-1,{0}}, #line 1464 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str876), {226, 137, 190, 0}}, {-1,{0}}, {-1,{0}}, #line 1733 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str879), {226, 138, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 1734 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str882), {226, 138, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1732 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str887), {226, 138, 143, 0}}, #line 1289 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str888), {226, 137, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 764 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str892), {240, 157, 149, 154}}, {-1,{0}}, #line 1425 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str894), {194, 177, 0}}, {-1,{0}}, #line 2019 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str896), {124, 0}}, {-1,{0}}, #line 1844 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str898), {207, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 986 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str901), {226, 151, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1033 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str905), {226, 134, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 922 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str920), {226, 170, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1615 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str934), {240, 157, 147, 135}}, #line 1477 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str935), {240, 157, 146, 172}}, #line 998 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str936), {240, 157, 147, 129}}, {-1,{0}}, #line 1742 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str938), {240, 157, 147, 136}}, {-1,{0}}, #line 1890 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str940), {240, 157, 146, 175}}, #line 2127 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str941), {240, 157, 146, 181}}, #line 527 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str942), {226, 132, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1974 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str947), {240, 157, 147, 138}}, {-1,{0}}, #line 1891 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str949), {240, 157, 147, 137}}, {-1,{0}}, #line 740 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str951), {226, 138, 183, 0}}, #line 296 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str952), {226, 136, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 2080 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str955), {240, 157, 146, 179}}, #line 2067 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str956), {206, 158, 0}}, {-1,{0}}, {-1,{0}}, #line 1252 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str959), {240, 157, 147, 131}}, #line 1135 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str960), {226, 136, 139, 0}}, #line 197 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str961), {240, 157, 146, 183}}, #line 1166 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str962), {226, 132, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 793 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str967), {240, 157, 146, 165}}, #line 1442 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str968), {226, 170, 175, 0}}, {-1,{0}}, {-1,{0}}, #line 1302 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str971), {226, 164, 131, 0}}, #line 87 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str972), {226, 128, 181, 0}}, #line 2057 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str973), {240, 157, 146, 178}}, {-1,{0}}, #line 1988 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str975), {207, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1258 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str984), {226, 136, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 392 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str991), {226, 140, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1467 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str997), {240, 157, 147, 133}}, #line 1408 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str998), {207, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2035 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1005), {240, 157, 146, 177}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1112 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1011), {226, 137, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1693 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1021), {226, 137, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1275 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1028), {226, 171, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1267 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1032), {226, 171, 133, 0}}, #line 440 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1033), {226, 140, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1520 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1038), {125, 0}}, #line 2036 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1039), {240, 157, 147, 139}}, #line 850 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1040), {123, 0}}, #line 396 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1041), {240, 157, 149, 149}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 585 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1049), {226, 129, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 930 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1055), {226, 137, 178, 0}}, {-1,{0}}, {-1,{0}}, #line 815 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1058), {240, 157, 146, 166}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1416 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1064), {226, 168, 162, 0}}, #line 1068 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1065), {226, 132, 179, 0}}, #line 1741 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1066), {240, 157, 146, 174}}, #line 1523 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1067), {226, 166, 142, 0}}, {-1,{0}}, #line 853 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1069), {226, 166, 143, 0}}, #line 1518 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1070), {226, 164, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 1717 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1073), {226, 138, 147, 0}}, #line 1503 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1074), {226, 135, 146, 0}}, #line 142 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1075), {226, 171, 173, 0}}, #line 835 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1076), {226, 135, 144, 0}}, {-1,{0}}, #line 587 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1078), {240, 157, 146, 187}}, #line 1973 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1079), {240, 157, 146, 176}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1905 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1087), {226, 135, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 1605 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1090), {226, 132, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2053 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1094), {240, 157, 149, 168}}, {-1,{0}}, {-1,{0}}, #line 442 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1097), {240, 157, 146, 159}}, #line 1351 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1098), {226, 166, 183, 0}}, #line 1662 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1099), {226, 164, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 362 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1103), {226, 136, 135, 0}}, #line 1485 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1104), {226, 135, 155, 0}}, #line 1558 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1105), {207, 129, 0}}, #line 817 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1106), {226, 135, 154, 0}}, #line 1437 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1107), {226, 137, 188, 0}}, #line 1478 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1108), {240, 157, 147, 134}}, {-1,{0}}, {-1,{0}}, #line 1028 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1111), {194, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1185 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1115), {226, 136, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 523 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1120), {226, 169, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1716 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1125), {226, 138, 147, 0}}, {-1,{0}}, #line 1259 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1127), {226, 136, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1340 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1131), {226, 167, 128, 0}}, #line 1514 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1132), {226, 136, 182, 0}}, #line 999 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1133), {226, 132, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 370 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1137), {226, 135, 131, 0}}, {-1,{0}}, #line 393 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1139), {226, 140, 141, 0}}, #line 408 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1140), {194, 168, 0}}, #line 404 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1141), {226, 136, 148, 0}}, #line 1358 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1142), {226, 136, 168, 0}}, {-1,{0}}, #line 2102 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1144), {240, 157, 146, 180}}, {-1,{0}}, {-1,{0}}, #line 562 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1147), {240, 157, 148, 189}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 304 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1152), {240, 157, 146, 158}}, #line 1336 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1153), {226, 134, 186, 0}}, #line 1243 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1154), {226, 134, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1026 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1159), {226, 137, 168, 0}}, #line 515 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1160), {226, 170, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1853 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1164), {195, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 516 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1169), {226, 170, 149, 0}}, {-1,{0}}, {-1,{0}}, #line 743 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1172), {226, 132, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1992 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1179), {226, 135, 149, 0}}, #line 1611 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1180), {226, 168, 146, 0}}, #line 441 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1181), {226, 140, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1387 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1187), {226, 136, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1356 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1195), {226, 134, 187, 0}}, #line 1744 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1196), {226, 140, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 412 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1200), {226, 171, 164, 0}}, #line 526 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1201), {226, 137, 147, 0}}, #line 381 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1202), {226, 153, 166, 0}}, #line 1743 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1203), {226, 136, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1368 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1208), {226, 147, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 769 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1212), {240, 157, 146, 190}}, #line 725 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1213), {226, 133, 136, 0}}, #line 1543 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1214), {226, 150, 173, 0}}, {-1,{0}}, {-1,{0}}, #line 1249 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1217), {226, 139, 161, 0}}, #line 1660 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1218), {194, 167, 0}}, {-1,{0}}, #line 1060 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1220), {226, 171, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1365 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1224), {226, 169, 150, 0}}, {-1,{0}}, #line 407 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1226), {226, 136, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 518 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1230), {61, 0}}, {-1,{0}}, #line 679 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1232), {94, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1745 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1236), {226, 139, 134, 0}}, #line 1069 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1237), {226, 136, 190, 0}}, {-1,{0}}, #line 382 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1239), {194, 168, 0}}, #line 1044 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1240), {226, 136, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 564 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1252), {226, 136, 128, 0}}, {-1,{0}}, {-1,{0}}, #line 1189 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1255), {226, 139, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1065 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1263), {240, 157, 149, 158}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1138 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1270), {226, 136, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2004 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1280), {226, 171, 169, 0}}, {-1,{0}}, #line 1251 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1282), {240, 157, 146, 169}}, {-1,{0}}, #line 1396 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1284), {46, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 102 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1292), {226, 136, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 112 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1298), {226, 137, 172, 0}}, #line 750 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1299), {226, 136, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 103 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1307), {226, 136, 181, 0}}, #line 1410 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1308), {207, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1551 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1326), {240, 157, 148, 175}}, #line 1471 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1327), {240, 157, 148, 148}}, #line 934 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1328), {240, 157, 148, 169}}, {-1,{0}}, #line 1667 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1330), {240, 157, 148, 176}}, #line 1148 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1331), {226, 134, 174, 0}}, #line 1836 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1332), {240, 157, 148, 151}}, #line 2121 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1333), {226, 132, 168, 0}}, #line 476 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1334), {240, 157, 148, 162}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1685 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1338), {226, 136, 188, 0}}, #line 1921 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1339), {240, 157, 148, 178}}, #line 1606 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1340), {226, 168, 174, 0}}, #line 1837 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1341), {240, 157, 148, 177}}, #line 980 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1342), {226, 168, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2063 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1347), {240, 157, 148, 155}}, {-1,{0}}, {-1,{0}}, #line 1538 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1350), {226, 132, 156, 0}}, #line 1119 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1351), {240, 157, 148, 171}}, {-1,{0}}, #line 114 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1353), {240, 157, 148, 159}}, {-1,{0}}, #line 1184 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1355), {226, 137, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 788 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1359), {240, 157, 148, 141}}, {-1,{0}}, #line 443 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1361), {240, 157, 146, 185}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2050 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1365), {240, 157, 148, 154}}, {-1,{0}}, #line 129 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1367), {226, 167, 171, 0}}, {-1,{0}}, #line 2125 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1369), {240, 157, 149, 171}}, #line 1541 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1370), {226, 132, 157, 0}}, {-1,{0}}, #line 1170 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1372), {226, 137, 173, 0}}, {-1,{0}}, {-1,{0}}, #line 1694 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1375), {226, 168, 164, 0}}, {-1,{0}}, #line 565 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1377), {226, 136, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1401 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1389), {240, 157, 148, 173}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1342 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1395), {197, 141, 0}}, {-1,{0}}, #line 2026 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1397), {240, 157, 148, 153}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 488 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1409), {196, 146, 0}}, #line 1616 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1410), {226, 132, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2058 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1414), {240, 157, 147, 140}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1679 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1423), {226, 134, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1664 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1429), {226, 136, 150, 0}}, {-1,{0}}, #line 2027 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1431), {240, 157, 148, 179}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 806 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1450), {240, 157, 148, 142}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1354 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1455), {226, 166, 185, 0}}, {-1,{0}}, #line 1047 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1457), {240, 157, 148, 144}}, #line 1666 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1458), {240, 157, 148, 150}}, {-1,{0}}, {-1,{0}}, #line 1160 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1461), {226, 139, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 588 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1467), {226, 132, 177, 0}}, {-1,{0}}, {-1,{0}}, #line 553 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1470), {240, 157, 148, 163}}, #line 1920 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1471), {240, 157, 148, 152}}, {-1,{0}}, #line 1676 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1473), {226, 136, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1304 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1488), {226, 136, 188, 0}}, #line 367 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1489), {240, 157, 148, 135}}, #line 920 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1490), {226, 139, 150, 0}}, {-1,{0}}, {-1,{0}}, #line 1458 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1493), {226, 140, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1472 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1500), {240, 157, 148, 174}}, #line 345 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1501), {226, 135, 147, 0}}, {-1,{0}}, #line 1247 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1503), {226, 139, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1678 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1507), {226, 134, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1840 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1515), {226, 136, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 357 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1519), {226, 133, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1839 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1524), {226, 136, 180, 0}}, #line 933 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1525), {240, 157, 148, 143}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1824 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1532), {226, 140, 150, 0}}, {-1,{0}}, {-1,{0}}, #line 483 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1535), {226, 136, 136, 0}}, #line 2096 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1536), {240, 157, 148, 156}}, #line 271 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1537), {226, 136, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1337 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1542), {226, 166, 190, 0}}, {-1,{0}}, #line 245 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1544), {226, 132, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 548 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1559), {226, 153, 128, 0}}, #line 1269 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1560), {226, 170, 176, 0}}, #line 1312 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1561), {226, 138, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1395 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1568), {37, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1362 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1578), {194, 170, 0}}, {-1,{0}}, #line 1359 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1580), {226, 169, 157, 0}}, #line 1557 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1581), {206, 161, 0}}, {-1,{0}}, #line 1067 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1583), {240, 157, 147, 130}}, {-1,{0}}, #line 1303 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1585), {226, 138, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 958 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1589), {226, 137, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1133 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1597), {226, 135, 142, 0}}, #line 1357 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1598), {226, 169, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 387 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1602), {195, 183, 0}}, {-1,{0}}, #line 721 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1604), {240, 157, 148, 166}}, #line 484 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1605), {226, 143, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 203 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1615), {92, 0}}, #line 1298 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1616), {226, 164, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 732 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1626), {196, 170, 0}}, {-1,{0}}, #line 89 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1628), {226, 139, 141, 0}}, #line 1898 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1629), {226, 137, 172, 0}}, #line 1338 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1630), {226, 166, 187, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1508 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1639), {226, 165, 180, 0}}, #line 409 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1640), {226, 135, 147, 0}}, #line 840 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1641), {226, 165, 179, 0}}, #line 491 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1642), {226, 136, 133, 0}}, #line 1350 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1643), {240, 157, 149, 160}}, {-1,{0}}, #line 540 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1645), {226, 136, 131, 0}}, {-1,{0}}, {-1,{0}}, #line 949 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1648), {226, 165, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 539 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1656), {33, 0}}, #line 503 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1657), {240, 157, 148, 188}}, #line 1142 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1658), {226, 135, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1849 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1663), {226, 128, 137, 0}}, #line 1218 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1664), {226, 138, 136, 0}}, #line 1403 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1665), {207, 134, 0}}, #line 410 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1666), {226, 135, 144, 0}}, {-1,{0}}, #line 1866 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1668), {226, 171, 177, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 386 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1672), {195, 183, 0}}, {-1,{0}}, #line 1118 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1674), {240, 157, 148, 145}}, #line 1144 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1675), {226, 137, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2128 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1689), {240, 157, 147, 143}}, #line 994 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1690), {226, 165, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 950 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1697), {226, 151, 186, 0}}, {-1,{0}}, {-1,{0}}, #line 1242 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1700), {226, 135, 143, 0}}, #line 1224 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1701), {226, 138, 137, 0}}, {-1,{0}}, #line 1819 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1703), {226, 135, 153, 0}}, #line 1847 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1704), {226, 129, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1931 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1708), {226, 151, 184, 0}}, #line 1204 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1709), {226, 139, 190, 0}}, {-1,{0}}, #line 1449 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1711), {226, 128, 178, 0}}, {-1,{0}}, {-1,{0}}, #line 1451 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1714), {226, 132, 153, 0}}, {-1,{0}}, #line 1334 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1716), {206, 169, 0}}, {-1,{0}}, {-1,{0}}, #line 264 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1719), {226, 138, 151, 0}}, #line 1159 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1720), {226, 139, 170, 0}}, {-1,{0}}, {-1,{0}}, #line 1691 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1723), {226, 170, 157, 0}}, #line 1307 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1724), {226, 135, 150, 0}}, {-1,{0}}, {-1,{0}}, #line 1989 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1727), {207, 150, 0}}, {-1,{0}}, {-1,{0}}, #line 1367 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1730), {226, 169, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1663 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1735), {226, 136, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 996 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1739), {226, 138, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1397 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1743), {226, 128, 176, 0}}, #line 1053 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1744), {226, 136, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1972 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1750), {226, 151, 185, 0}}, {-1,{0}}, {-1,{0}}, #line 368 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1753), {240, 157, 148, 161}}, #line 1049 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1754), {226, 132, 167, 0}}, #line 1447 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1755), {226, 170, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2040 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1759), {226, 138, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 1246 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1762), {226, 139, 171, 0}}, #line 2038 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1763), {226, 138, 138, 0}}, {-1,{0}}, #line 472 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1765), {226, 137, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 918 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1778), {226, 170, 147, 0}}, {-1,{0}}, {-1,{0}}, #line 86 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1781), {207, 182, 0}}, {-1,{0}}, #line 1512 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1783), {226, 164, 154, 0}}, {-1,{0}}, #line 842 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1785), {226, 164, 153, 0}}, {-1,{0}}, {-1,{0}}, #line 1953 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1788), {226, 165, 174, 0}}, {-1,{0}}, {-1,{0}}, #line 510 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1791), {206, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1963 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1796), {207, 133, 0}}, {-1,{0}}, #line 1051 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1798), {42, 0}}, #line 697 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1799), {226, 132, 141, 0}}, #line 2028 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1800), {226, 138, 178, 0}}, {-1,{0}}, #line 1552 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1802), {226, 132, 156, 0}}, {-1,{0}}, {-1,{0}}, #line 2047 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1805), {226, 139, 128, 0}}, #line 2051 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1806), {240, 157, 148, 180}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 93 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1812), {226, 140, 133, 0}}, {-1,{0}}, {-1,{0}}, #line 1030 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1815), {226, 156, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 250 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1820), {206, 167, 0}}, #line 493 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1821), {226, 136, 133, 0}}, #line 1202 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1822), {226, 136, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 925 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1827), {226, 137, 182, 0}}, {-1,{0}}, #line 377 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1829), {226, 139, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2034 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1842), {226, 138, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 262 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1849), {226, 138, 150, 0}}, {-1,{0}}, #line 1341 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1851), {197, 140, 0}}, #line 1658 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1852), {226, 135, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 552 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1859), {240, 157, 148, 137}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1444 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1865), {226, 170, 181, 0}}, {-1,{0}}, #line 379 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1867), {226, 139, 132, 0}}, #line 1363 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1868), {194, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1102 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1873), {226, 135, 151, 0}}, #line 763 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1874), {240, 157, 149, 128}}, #line 259 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1875), {226, 138, 153, 0}}, {-1,{0}}, {-1,{0}}, #line 1452 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1878), {226, 170, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 403 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1884), {226, 136, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1253 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1903), {226, 136, 164, 0}}, {-1,{0}}, #line 147 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1905), {226, 138, 165, 0}}, {-1,{0}}, #line 1427 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1907), {226, 168, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1736 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1917), {226, 138, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 792 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1925), {240, 157, 149, 155}}, {-1,{0}}, {-1,{0}}, #line 1962 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1928), {206, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 278 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1936), {226, 169, 180, 0}}, {-1,{0}}, #line 1300 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1938), {60, 0}}, {-1,{0}}, {-1,{0}}, #line 1114 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1941), {226, 137, 170, 0}}, #line 277 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1942), {226, 136, 183, 0}}, {-1,{0}}, {-1,{0}}, #line 204 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1945), {226, 159, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 411 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1949), {226, 135, 148, 0}}, #line 1423 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1950), {226, 168, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 734 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1959), {226, 132, 145, 0}}, #line 480 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1960), {226, 170, 150, 0}}, {-1,{0}}, {-1,{0}}, #line 1370 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1963), {226, 132, 180, 0}}, #line 1821 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1964), {226, 164, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2116 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1969), {226, 132, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1031 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1973), {226, 156, 160, 0}}, {-1,{0}}, #line 1048 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1975), {240, 157, 148, 170}}, #line 1504 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1976), {226, 164, 158, 0}}, #line 528 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1977), {226, 132, 176, 0}}, #line 836 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1978), {226, 164, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1062 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1985), {226, 136, 147, 0}}, #line 1129 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1986), {226, 137, 175, 0}}, #line 1130 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1987), {226, 137, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 627 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str1996), {226, 137, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 380 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2003), {226, 153, 166, 0}}, #line 655 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2004), {62, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 928 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2014), {226, 137, 178, 0}}, #line 446 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2015), {226, 167, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1954 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2023), {226, 134, 191, 0}}, #line 1731 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2024), {226, 138, 147, 0}}, #line 1003 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2025), {226, 170, 141, 0}}, {-1,{0}}, #line 1157 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2027), {226, 137, 170, 0}}, {-1,{0}}, #line 1194 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2029), {226, 137, 174, 0}}, {-1,{0}}, #line 630 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2031), {226, 170, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1634 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2035), {226, 170, 184, 0}}, {-1,{0}}, {-1,{0}}, #line 1036 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2038), {226, 134, 164, 0}}, #line 1197 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2039), {226, 137, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1550 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2043), {226, 140, 139, 0}}, {-1,{0}}, #line 932 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2045), {226, 140, 138, 0}}, {-1,{0}}, {-1,{0}}, #line 1256 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2048), {226, 137, 132, 0}}, {-1,{0}}, #line 201 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2050), {226, 139, 141, 0}}, #line 1195 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2051), {226, 137, 176, 0}}, #line 1199 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2052), {226, 137, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1089 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2056), {226, 169, 131, 0}}, {-1,{0}}, {-1,{0}}, #line 1196 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2059), {226, 137, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1448 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2070), {226, 137, 190, 0}}, {-1,{0}}, #line 976 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2072), {226, 134, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1432 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2076), {226, 170, 187, 0}}, #line 1530 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2077), {125, 0}}, #line 1037 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2078), {226, 134, 165, 0}}, #line 860 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2079), {123, 0}}, {-1,{0}}, #line 2120 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2081), {240, 157, 148, 183}}, {-1,{0}}, {-1,{0}}, #line 1946 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2084), {226, 134, 145, 0}}, {-1,{0}}, #line 632 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2086), {226, 170, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1640 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2090), {226, 170, 176, 0}}, #line 739 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2091), {226, 132, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1526 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2096), {197, 153, 0}}, {-1,{0}}, #line 856 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2098), {196, 190, 0}}, #line 1349 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2099), {240, 157, 149, 134}}, #line 1636 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2100), {197, 161, 0}}, #line 88 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2101), {226, 136, 189, 0}}, #line 1828 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2102), {197, 164, 0}}, #line 2110 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2103), {197, 189, 0}}, #line 462 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2104), {196, 155, 0}}, {-1,{0}}, #line 108 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2106), {226, 132, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1121 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2110), {226, 137, 177, 0}}, #line 1829 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2111), {197, 165, 0}}, {-1,{0}}, #line 566 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2113), {226, 139, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 701 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2119), {226, 132, 139, 0}}, {-1,{0}}, #line 1091 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2121), {197, 136, 0}}, #line 487 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2122), {226, 170, 151, 0}}, {-1,{0}}, #line 1827 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2124), {226, 142, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1886 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2128), {226, 168, 185, 0}}, {-1,{0}}, {-1,{0}}, #line 378 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2131), {226, 139, 132, 0}}, {-1,{0}}, {-1,{0}}, #line 1096 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2134), {226, 169, 130, 0}}, {-1,{0}}, #line 96 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2136), {226, 142, 181, 0}}, {-1,{0}}, #line 586 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2138), {226, 140, 162, 0}}, #line 128 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2139), {226, 164, 141, 0}}, {-1,{0}}, #line 1713 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2141), {226, 153, 160, 0}}, {-1,{0}}, #line 1469 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2143), {207, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 144 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2150), {240, 157, 148, 185}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 394 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2156), {36, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 385 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2164), {226, 139, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1714 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2170), {226, 153, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1225 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2176), {226, 137, 129, 0}}, #line 406 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2177), {226, 140, 134, 0}}, {-1,{0}}, #line 594 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2179), {226, 170, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 97 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2186), {226, 142, 182, 0}}, {-1,{0}}, {-1,{0}}, #line 1820 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2189), {226, 134, 153, 0}}, #line 106 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2190), {207, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 770 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2194), {226, 132, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1227 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2198), {226, 137, 135, 0}}, #line 513 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2199), {226, 137, 149, 0}}, {-1,{0}}, {-1,{0}}, #line 1863 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2202), {226, 136, 173, 0}}, {-1,{0}}, {-1,{0}}, #line 756 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2205), {226, 168, 188, 0}}, {-1,{0}}, #line 1271 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2207), {226, 171, 134, 0}}, {-1,{0}}, {-1,{0}}, #line 1308 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2210), {226, 134, 150, 0}}, #line 1263 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2211), {226, 171, 133, 0}}, {-1,{0}}, {-1,{0}}, #line 1125 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2214), {226, 169, 190, 0}}, {-1,{0}}, #line 1948 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2216), {226, 135, 145, 0}}, #line 604 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2217), {226, 137, 165, 0}}, #line 1352 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2218), {226, 128, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1698 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2223), {226, 136, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1635 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2228), {197, 160, 0}}, {-1,{0}}, #line 1301 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2230), {226, 138, 180, 0}}, #line 612 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2231), {226, 169, 190, 0}}, #line 135 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2232), {226, 144, 163, 0}}, #line 1484 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2233), {34, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 139 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2238), {226, 150, 136, 0}}, #line 1873 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2239), {226, 132, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 794 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2245), {240, 157, 146, 191}}, #line 2046 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2246), {226, 136, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 29 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2254), {196, 128, 0}}, {-1,{0}}, #line 517 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2256), {226, 169, 181, 0}}, {-1,{0}}, {-1,{0}}, #line 351 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2259), {196, 142, 0}}, {-1,{0}}, {-1,{0}}, #line 399 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2262), {226, 131, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 634 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2270), {226, 170, 136, 0}}, #line 1990 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2271), {226, 136, 157, 0}}, {-1,{0}}, #line 635 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2273), {226, 137, 169, 0}}, #line 1461 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2274), {226, 136, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 774 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2279), {226, 139, 180, 0}}, {-1,{0}}, #line 469 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2281), {226, 169, 183, 0}}, #line 771 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2282), {226, 136, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1885 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2286), {226, 131, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 568 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2290), {226, 132, 177, 0}}, #line 1462 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2291), {226, 136, 183, 0}}, {-1,{0}}, {-1,{0}}, #line 1122 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2294), {226, 137, 177, 0}}, #line 855 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2295), {196, 189, 0}}, {-1,{0}}, #line 1123 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2297), {226, 137, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 870 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2313), {226, 137, 166, 0}}, #line 227 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2314), {196, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 199 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2320), {226, 129, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1463 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2326), {226, 136, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 914 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2331), {226, 169, 191, 0}}, #line 291 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2332), {226, 136, 175, 0}}, {-1,{0}}, #line 35 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2334), {226, 169, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1659 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2338), {226, 134, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1366 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2343), {226, 169, 151, 0}}, #line 676 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2344), {226, 134, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 845 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2350), {226, 170, 173, 0}}, {-1,{0}}, #line 243 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2352), {194, 183, 0}}, {-1,{0}}, {-1,{0}}, #line 1328 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2355), {240, 157, 148, 172}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1103 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2359), {226, 134, 151, 0}}, {-1,{0}}, #line 1473 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2361), {226, 168, 140, 0}}, {-1,{0}}, {-1,{0}}, #line 846 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2364), {226, 170, 173, 0}}, #line 801 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2365), {207, 176, 0}}, {-1,{0}}, {-1,{0}}, #line 698 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2368), {226, 128, 149, 0}}, #line 475 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2369), {240, 157, 148, 136}}, #line 692 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2370), {226, 135, 191, 0}}, #line 1239 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2371), {226, 170, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 747 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2377), {196, 177, 0}}, {-1,{0}}, #line 1915 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2379), {226, 135, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 608 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2386), {226, 137, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1257 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2391), {226, 137, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 609 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2404), {226, 137, 167, 0}}, {-1,{0}}, {-1,{0}}, #line 474 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2407), {226, 137, 146, 0}}, {-1,{0}}, {-1,{0}}, #line 1610 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2410), {226, 166, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1369 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2419), {240, 157, 146, 170}}, {-1,{0}}, {-1,{0}}, #line 1418 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2422), {226, 136, 148, 0}}, {-1,{0}}, {-1,{0}}, #line 821 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2425), {226, 132, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1846 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2429), {226, 136, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1445 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2440), {226, 139, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1090 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2444), {197, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1079 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2449), {226, 169, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 727 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2457), {226, 136, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 198 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2470), {226, 132, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1035 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2483), {226, 134, 167, 0}}, {-1,{0}}, {-1,{0}}, #line 1993 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2486), {207, 177, 0}}, {-1,{0}}, #line 775 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2488), {226, 139, 179, 0}}, {-1,{0}}, {-1,{0}}, #line 1296 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2491), {226, 164, 132, 0}}, {-1,{0}}, {-1,{0}}, #line 1191 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2494), {226, 167, 143, 0}}, {-1,{0}}, #line 520 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2496), {226, 137, 159, 0}}, {-1,{0}}, #line 1193 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2498), {226, 139, 172, 0}}, #line 1192 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2499), {226, 139, 170, 0}}, {-1,{0}}, {-1,{0}}, #line 60 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2502), {240, 157, 148, 184}}, #line 680 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2503), {226, 132, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1984 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2507), {226, 166, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 688 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2511), {226, 132, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1494 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2517), {226, 166, 165, 0}}, #line 1704 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2518), {226, 170, 172, 0}}, #line 1002 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2519), {226, 137, 178, 0}}, {-1,{0}}, #line 1234 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2521), {226, 168, 148, 0}}, {-1,{0}}, #line 352 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2523), {196, 143, 0}}, {-1,{0}}, #line 531 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2525), {226, 137, 130, 0}}, {-1,{0}}, #line 1939 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2527), {226, 139, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1705 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2532), {226, 170, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 814 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2536), {240, 157, 149, 156}}, #line 638 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2537), {240, 157, 149, 152}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1255 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2542), {226, 137, 129, 0}}, {-1,{0}}, #line 200 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2544), {226, 136, 189, 0}}, {-1,{0}}, #line 1697 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2546), {226, 136, 152, 0}}, {-1,{0}}, #line 1171 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2548), {226, 136, 166, 0}}, #line 1200 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2549), {226, 170, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 519 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2565), {226, 137, 130, 0}}, {-1,{0}}, {-1,{0}}, #line 1186 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2568), {226, 139, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1525 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2572), {197, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1429 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2577), {226, 132, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 637 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2583), {240, 157, 148, 190}}, {-1,{0}}, {-1,{0}}, #line 722 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2586), {226, 132, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 2048 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2589), {226, 137, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1455 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2595), {226, 136, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1373 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2617), {226, 138, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 418 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2624), {226, 135, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 289 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2627), {226, 137, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 636 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2631), {226, 139, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1650 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2635), {226, 137, 191, 0}}, {-1,{0}}, #line 789 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2637), {240, 157, 148, 167}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1961 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2645), {207, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1155 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2650), {226, 139, 152, 0}}, {-1,{0}}, {-1,{0}}, #line 419 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2653), {226, 135, 149, 0}}, {-1,{0}}, #line 1127 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2655), {226, 137, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 683 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2664), {226, 153, 165, 0}}, {-1,{0}}, #line 921 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2666), {226, 139, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1111 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2670), {226, 164, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 541 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2676), {226, 136, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1702 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2687), {226, 140, 163, 0}}, {-1,{0}}, #line 1983 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2689), {226, 166, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 684 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2693), {226, 153, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 699 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2700), {226, 148, 128, 0}}, {-1,{0}}, {-1,{0}}, #line 644 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2703), {226, 137, 183, 0}}, {-1,{0}}, #line 1614 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2705), {226, 128, 186, 0}}, {-1,{0}}, #line 997 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2707), {226, 128, 185, 0}}, {-1,{0}}, #line 1539 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2709), {226, 132, 155, 0}}, #line 347 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2710), {226, 171, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1686 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2714), {226, 169, 170, 0}}, #line 640 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2715), {226, 137, 165, 0}}, #line 646 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2716), {226, 137, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 641 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2721), {226, 139, 155, 0}}, {-1,{0}}, #line 643 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2723), {226, 170, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1529 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2737), {226, 140, 137, 0}}, {-1,{0}}, #line 859 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2739), {226, 140, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 926 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2743), {226, 137, 182, 0}}, {-1,{0}}, {-1,{0}}, #line 1339 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2746), {226, 128, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1851 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2753), {226, 136, 188, 0}}, {-1,{0}}, #line 758 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2755), {226, 129, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1486 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2762), {226, 136, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 768 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2766), {194, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 736 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2774), {226, 132, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1965 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2779), {226, 138, 165, 0}}, {-1,{0}}, #line 1052 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2781), {226, 171, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1326 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2790), {226, 166, 191, 0}}, {-1,{0}}, {-1,{0}}, #line 356 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2793), {226, 135, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1493 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2800), {226, 166, 146, 0}}, {-1,{0}}, #line 826 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2802), {226, 166, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 521 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2808), {226, 135, 140, 0}}, #line 1389 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2809), {226, 171, 179, 0}}, #line 2011 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2810), {226, 171, 166, 0}}, #line 1327 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2811), {240, 157, 148, 146}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 104 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2816), {226, 136, 181, 0}}, {-1,{0}}, #line 1513 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2818), {226, 164, 156, 0}}, {-1,{0}}, #line 843 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2820), {226, 164, 155, 0}}, #line 1348 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2821), {226, 138, 150, 0}}, #line 73 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2822), {240, 157, 146, 156}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 509 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2826), {206, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1675 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2832), {226, 134, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 776 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2845), {226, 136, 136, 0}}, {-1,{0}}, #line 1050 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2847), {194, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2111 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2851), {197, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 816 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2856), {240, 157, 147, 128}}, #line 648 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2857), {226, 132, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 113 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2862), {240, 157, 148, 133}}, #line 607 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2863), {226, 139, 155, 0}}, #line 686 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2864), {226, 138, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1884 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2871), {226, 168, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 479 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2877), {195, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1654 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2881), {226, 139, 133, 0}}, #line 1923 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2882), {195, 185, 0}}, {-1,{0}}, #line 2114 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2884), {197, 187, 0}}, #line 471 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2885), {196, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1228 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2890), {226, 137, 137, 0}}, {-1,{0}}, #line 1834 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2892), {226, 131, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1466 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2897), {240, 157, 146, 171}}, #line 1407 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2898), {206, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 647 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2903), {240, 157, 146, 162}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1424 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2910), {226, 168, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1172 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2914), {226, 136, 137, 0}}, {-1,{0}}, #line 1421 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2916), {194, 177, 0}}, {-1,{0}}, {-1,{0}}, #line 696 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2919), {240, 157, 149, 153}}, #line 593 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2920), {207, 157, 0}}, {-1,{0}}, #line 1043 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2922), {226, 136, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 388 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2926), {226, 139, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 400 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2940), {226, 137, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1985 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2956), {207, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1438 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2963), {226, 137, 186, 0}}, {-1,{0}}, {-1,{0}}, #line 592 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2966), {207, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 348 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2974), {226, 138, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1169 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2979), {226, 137, 162, 0}}, {-1,{0}}, {-1,{0}}, #line 1910 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2982), {197, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1332 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2990), {226, 167, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1608 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str2994), {226, 165, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1440 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3002), {226, 137, 188, 0}}, {-1,{0}}, {-1,{0}}, #line 1687 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3005), {226, 137, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1922 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3014), {195, 153, 0}}, {-1,{0}}, #line 349 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3016), {226, 164, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1655 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3021), {226, 169, 166, 0}}, {-1,{0}}, #line 2015 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3023), {226, 137, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1034 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3027), {226, 134, 166, 0}}, {-1,{0}}, {-1,{0}}, #line 1861 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3030), {195, 151, 0}}, {-1,{0}}, {-1,{0}}, #line 1495 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3033), {226, 159, 169, 0}}, {-1,{0}}, #line 827 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3035), {226, 159, 168, 0}}, {-1,{0}}, {-1,{0}}, #line 877 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3038), {226, 134, 162, 0}}, #line 672 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3039), {226, 132, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1918 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3044), {226, 165, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1137 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3053), {226, 139, 186, 0}}, {-1,{0}}, #line 1549 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3055), {226, 165, 189, 0}}, {-1,{0}}, #line 931 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3057), {226, 165, 188, 0}}, #line 675 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3058), {226, 165, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1353 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3066), {226, 128, 152, 0}}, {-1,{0}}, #line 1919 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3068), {226, 165, 190, 0}}, #line 1183 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3069), {226, 137, 142, 0}}, {-1,{0}}, {-1,{0}}, #line 895 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3072), {226, 138, 163, 0}}, {-1,{0}}, #line 1617 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3074), {226, 134, 177, 0}}, {-1,{0}}, #line 1000 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3076), {226, 134, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 667 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3080), {226, 137, 169, 0}}, {-1,{0}}, {-1,{0}}, #line 1860 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3083), {226, 138, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1649 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3092), {226, 168, 147, 0}}, {-1,{0}}, {-1,{0}}, #line 236 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3095), {196, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 454 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3103), {226, 166, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1909 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3114), {197, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 904 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3132), {226, 134, 191, 0}}, {-1,{0}}, {-1,{0}}, #line 903 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3135), {226, 165, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 461 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3139), {196, 154, 0}}, {-1,{0}}, {-1,{0}}, #line 693 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3142), {226, 136, 187, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 724 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3147), {195, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1238 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3155), {226, 170, 175, 0}}, #line 466 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3156), {226, 137, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 358 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3167), {226, 133, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1688 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3174), {226, 137, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1187 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3179), {226, 139, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 119 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3198), {226, 168, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 21 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3214), {240, 157, 148, 132}}, #line 873 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3215), {226, 134, 144, 0}}, #line 1335 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3216), {226, 136, 174, 0}}, {-1,{0}}, #line 1823 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3218), {9, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1329 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3227), {203, 155, 0}}, {-1,{0}}, {-1,{0}}, #line 1012 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3230), {60, 0}}, #line 1149 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3231), {226, 135, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1498 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3235), {226, 135, 165, 0}}, {-1,{0}}, #line 831 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3237), {226, 135, 164, 0}}, {-1,{0}}, #line 700 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3239), {240, 157, 146, 189}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 901 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3246), {226, 165, 145, 0}}, {-1,{0}}, #line 807 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3248), {240, 157, 148, 168}}, #line 619 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3249), {240, 157, 148, 164}}, #line 1945 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3250), {226, 164, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1250 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3259), {226, 170, 176, 0}}, #line 1015 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3260), {226, 139, 150, 0}}, #line 616 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3261), {226, 139, 155, 0}}, #line 2073 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3262), {226, 168, 128, 0}}, #line 1747 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3263), {226, 152, 134, 0}}, {-1,{0}}, {-1,{0}}, #line 983 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3266), {95, 0}}, {-1,{0}}, #line 2065 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3268), {226, 159, 183, 0}}, #line 465 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3269), {226, 137, 150, 0}}, {-1,{0}}, #line 1975 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3271), {226, 139, 176, 0}}, #line 1085 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3272), {226, 153, 174, 0}}, #line 1001 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3273), {226, 134, 176, 0}}, #line 745 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3274), {226, 136, 158, 0}}, {-1,{0}}, #line 283 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3276), {226, 136, 129, 0}}, {-1,{0}}, #line 1684 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3278), {207, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2077 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3285), {226, 168, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1400 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3289), {240, 157, 148, 147}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 618 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3295), {240, 157, 148, 138}}, {-1,{0}}, {-1,{0}}, #line 115 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3298), {226, 139, 130, 0}}, {-1,{0}}, #line 1692 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3300), {226, 170, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 726 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3319), {226, 168, 140, 0}}, #line 95 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3320), {226, 140, 133, 0}}, #line 94 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3321), {226, 140, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2069 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3329), {226, 159, 181, 0}}, #line 923 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3330), {226, 139, 154, 0}}, {-1,{0}}, #line 301 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3332), {226, 134, 181, 0}}, #line 772 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3333), {226, 139, 181, 0}}, {-1,{0}}, #line 282 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3335), {64, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1054 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3342), {194, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 916 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3349), {226, 170, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1683 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3356), {207, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1499 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3366), {226, 164, 160, 0}}, {-1,{0}}, #line 832 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3368), {226, 164, 159, 0}}, {-1,{0}}, {-1,{0}}, #line 2078 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3371), {226, 159, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 117 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3376), {226, 139, 131, 0}}, {-1,{0}}, #line 274 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3378), {226, 153, 163, 0}}, #line 677 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3379), {226, 135, 148, 0}}, #line 1625 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3380), {226, 138, 181, 0}}, {-1,{0}}, #line 1021 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3382), {226, 138, 180, 0}}, #line 741 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3383), {198, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 502 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3388), {196, 153, 0}}, #line 1630 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3389), {226, 132, 158, 0}}, #line 1023 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3390), {226, 166, 150, 0}}, #line 1746 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3391), {226, 139, 134, 0}}, {-1,{0}}, #line 1942 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3393), {197, 179, 0}}, {-1,{0}}, {-1,{0}}, #line 1855 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3396), {226, 136, 188, 0}}, {-1,{0}}, #line 671 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3398), {194, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1854 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3405), {203, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 875 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3412), {226, 135, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 617 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3417), {226, 170, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 217 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3422), {226, 136, 169, 0}}, #line 1751 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3423), {194, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1014 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3427), {226, 137, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1453 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3439), {226, 170, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1726 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3447), {226, 138, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1727 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3462), {226, 138, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1882 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3467), {226, 151, 172, 0}}, #line 1360 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3468), {226, 132, 180, 0}}, {-1,{0}}, {-1,{0}}, #line 222 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3471), {226, 136, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 302 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3475), {226, 156, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 366 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3482), {226, 165, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2071 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3487), {226, 159, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1725 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3491), {226, 138, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1624 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3503), {226, 150, 185, 0}}, {-1,{0}}, #line 1020 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3505), {226, 151, 131, 0}}, #line 777 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3506), {226, 129, 162, 0}}, #line 1598 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3507), {226, 142, 177, 0}}, {-1,{0}}, #line 954 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3509), {226, 142, 176, 0}}, #line 633 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3510), {226, 137, 169, 0}}, #line 936 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3511), {226, 170, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 1641 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3514), {226, 170, 180, 0}}, {-1,{0}}, #line 1978 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3516), {226, 150, 181, 0}}, {-1,{0}}, #line 2016 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3518), {226, 139, 174, 0}}, {-1,{0}}, #line 534 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3520), {195, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 952 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3523), {197, 128, 0}}, {-1,{0}}, #line 1941 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3525), {197, 178, 0}}, #line 300 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3526), {226, 136, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1120 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3534), {226, 137, 167, 0}}, #line 1309 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3535), {226, 164, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 917 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3543), {226, 139, 154, 0}}, {-1,{0}}, {-1,{0}}, #line 1415 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3546), {226, 138, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1618 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3550), {226, 134, 177, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 299 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3555), {226, 132, 151, 0}}, {-1,{0}}, #line 746 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3557), {226, 167, 157, 0}}, {-1,{0}}, #line 738 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3559), {196, 177, 0}}, #line 530 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3560), {226, 169, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1402 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3565), {206, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 628 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3573), {226, 170, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2030 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3579), {226, 138, 131, 0}}, {-1,{0}}, {-1,{0}}, #line 1690 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3582), {226, 170, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 413 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3586), {226, 159, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 414 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3591), {226, 159, 186, 0}}, {-1,{0}}, {-1,{0}}, #line 1295 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3594), {62, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1046 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3607), {226, 132, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1450 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3611), {226, 128, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 728 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3615), {226, 167, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1546 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3620), {226, 136, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 492 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3627), {226, 151, 187, 0}}, #line 1489 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3628), {226, 136, 154, 0}}, {-1,{0}}, {-1,{0}}, #line 687 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3631), {240, 157, 148, 165}}, #line 2115 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3632), {197, 188, 0}}, #line 1029 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3633), {226, 153, 130, 0}}, {-1,{0}}, #line 1500 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3635), {226, 164, 179, 0}}, #line 1436 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3636), {226, 137, 186, 0}}, #line 1646 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3637), {226, 170, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 383 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3641), {226, 133, 134, 0}}, {-1,{0}}, #line 1063 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3643), {226, 138, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1011 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3657), {226, 169, 185, 0}}, #line 762 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3658), {196, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 216 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3665), {226, 169, 139, 0}}, {-1,{0}}, #line 720 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3667), {226, 135, 148, 0}}, {-1,{0}}, #line 360 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3669), {226, 169, 183, 0}}, {-1,{0}}, #line 263 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3671), {226, 138, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1622 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3676), {226, 139, 140, 0}}, {-1,{0}}, #line 1016 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3678), {226, 139, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 1441 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3681), {226, 137, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 449 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3685), {226, 139, 177, 0}}, {-1,{0}}, #line 275 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3687), {226, 153, 163, 0}}, {-1,{0}}, #line 1488 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3689), {197, 149, 0}}, {-1,{0}}, #line 819 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3691), {196, 186, 0}}, #line 1889 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3692), {226, 143, 162, 0}}, #line 1632 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3693), {197, 155, 0}}, {-1,{0}}, {-1,{0}}, #line 2108 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3696), {197, 185, 0}}, #line 459 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3697), {195, 169, 0}}, {-1,{0}}, #line 1858 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3699), {226, 137, 136, 0}}, {-1,{0}}, #line 1906 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3701), {226, 165, 137, 0}}, #line 1902 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3702), {195, 186, 0}}, #line 982 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3703), {226, 136, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1076 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3714), {197, 132, 0}}, {-1,{0}}, #line 1206 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3716), {226, 138, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 951 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3720), {196, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1947 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3725), {226, 134, 145, 0}}, {-1,{0}}, #line 1511 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3727), {226, 134, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 438 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3738), {226, 138, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 555 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3742), {226, 151, 188, 0}}, #line 219 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3743), {226, 169, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 642 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3749), {226, 137, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1299 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3756), {226, 137, 164, 0}}, {-1,{0}}, #line 1883 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3758), {226, 137, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1346 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3764), {206, 191, 0}}, {-1,{0}}, #line 417 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3766), {226, 138, 168, 0}}, #line 233 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3767), {226, 136, 176, 0}}, #line 1621 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3768), {226, 128, 153, 0}}, {-1,{0}}, #line 1007 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3770), {226, 128, 154, 0}}, {-1,{0}}, #line 2124 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3772), {226, 135, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 293 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3780), {240, 157, 149, 148}}, {-1,{0}}, #line 292 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3782), {226, 136, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 670 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3798), {226, 128, 138, 0}}, #line 1728 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3799), {226, 138, 146, 0}}, #line 306 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3800), {226, 171, 143, 0}}, #line 1955 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3801), {226, 134, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 426 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3805), {204, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1674 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3817), {226, 134, 147, 0}}, {-1,{0}}, #line 2075 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3819), {240, 157, 149, 169}}, {-1,{0}}, #line 1631 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3821), {197, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2039 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3829), {226, 171, 140, 0}}, #line 265 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3830), {226, 151, 139, 0}}, #line 1414 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3831), {226, 168, 163, 0}}, #line 308 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3832), {226, 171, 144, 0}}, #line 2037 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3833), {226, 171, 139, 0}}, #line 1901 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3834), {195, 154, 0}}, {-1,{0}}, #line 773 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3836), {226, 139, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 606 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3845), {226, 170, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1719 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3851), {226, 138, 148, 0}}, {-1,{0}}, #line 1701 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3853), {226, 136, 163, 0}}, {-1,{0}}, #line 935 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3855), {226, 137, 182, 0}}, {-1,{0}}, #line 415 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3857), {226, 159, 185, 0}}, #line 1208 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3858), {226, 139, 160, 0}}, {-1,{0}}, {-1,{0}}, #line 477 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3861), {226, 170, 154, 0}}, {-1,{0}}, {-1,{0}}, #line 33 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3864), {38, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1162 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3874), {226, 136, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1862 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3883), {226, 168, 176, 0}}, {-1,{0}}, {-1,{0}}, #line 433 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3886), {226, 134, 189, 0}}, #line 2130 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3887), {226, 128, 140, 0}}, #line 818 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3888), {196, 185, 0}}, #line 432 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3889), {226, 165, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1331 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3898), {195, 178, 0}}, #line 2087 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3899), {195, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1718 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3903), {226, 138, 148, 0}}, {-1,{0}}, {-1,{0}}, #line 1322 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3906), {226, 138, 153, 0}}, #line 212 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3907), {196, 134, 0}}, {-1,{0}}, #line 1285 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3909), {206, 189, 0}}, #line 1888 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3910), {226, 168, 187, 0}}, {-1,{0}}, #line 478 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3912), {195, 136, 0}}, #line 507 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3913), {226, 169, 177, 0}}, {-1,{0}}, #line 85 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3915), {226, 137, 140, 0}}, {-1,{0}}, {-1,{0}}, #line 1956 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3918), {226, 138, 142, 0}}, {-1,{0}}, #line 470 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3920), {196, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 309 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3924), {226, 171, 146, 0}}, {-1,{0}}, #line 1689 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3926), {226, 170, 158, 0}}, #line 1958 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3927), {226, 134, 151, 0}}, #line 307 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3928), {226, 171, 145, 0}}, {-1,{0}}, #line 450 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3930), {226, 150, 191, 0}}, #line 1454 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3931), {226, 139, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 177 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3936), {226, 149, 153, 0}}, #line 1980 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3937), {226, 135, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 431 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3945), {226, 165, 158, 0}}, #line 650 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3946), {226, 170, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 120 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3950), {226, 168, 130, 0}}, #line 341 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3951), {226, 128, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 754 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3954), {226, 139, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 710 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3967), {195, 173, 0}}, {-1,{0}}, #line 1434 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3969), {226, 137, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 481 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3981), {226, 170, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 742 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3987), {226, 135, 146, 0}}, #line 2010 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3988), {226, 138, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 207 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str3996), {226, 137, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1070 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4015), {206, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2008 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4022), {226, 138, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1027 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4028), {226, 137, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 894 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4033), {226, 134, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1075 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4037), {197, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1936 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4042), {226, 143, 159, 0}}, #line 1468 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4043), {206, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1559 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4047), {207, 177, 0}}, {-1,{0}}, #line 912 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4049), {226, 170, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1789 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4055), {194, 185, 0}}, {-1,{0}}, {-1,{0}}, #line 1790 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4058), {194, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1791 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4066), {194, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 118 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4071), {226, 168, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 424 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4078), {226, 135, 147, 0}}, {-1,{0}}, #line 2082 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4080), {226, 168, 134, 0}}, {-1,{0}}, #line 92 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4082), {226, 138, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1106 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4087), {226, 128, 139, 0}}, #line 209 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4088), {226, 137, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 305 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4100), {240, 157, 146, 184}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1248 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4109), {226, 138, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1792 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4115), {226, 138, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 238 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4122), {194, 184, 0}}, {-1,{0}}, {-1,{0}}, #line 191 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4125), {226, 149, 159, 0}}, {-1,{0}}, #line 1364 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4127), {226, 138, 182, 0}}, #line 2129 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4128), {226, 128, 141, 0}}, #line 723 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4129), {195, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 716 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4137), {196, 176, 0}}, {-1,{0}}, #line 2081 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4139), {240, 157, 147, 141}}, #line 2068 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4140), {206, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1131 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4144), {226, 137, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 165 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4153), {226, 149, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1852 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4163), {195, 158, 0}}, {-1,{0}}, #line 1487 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4165), {197, 148, 0}}, {-1,{0}}, #line 1505 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4167), {226, 134, 170, 0}}, {-1,{0}}, #line 837 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4169), {226, 134, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1627 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4177), {226, 167, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 180 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4189), {226, 149, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 340 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4215), {226, 128, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1345 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4220), {206, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 420 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4226), {226, 136, 165, 0}}, {-1,{0}}, {-1,{0}}, #line 1117 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4229), {226, 136, 132, 0}}, {-1,{0}}, {-1,{0}}, #line 1284 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4232), {206, 157, 0}}, #line 1116 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4233), {226, 136, 132, 0}}, #line 605 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4234), {226, 137, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 63 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4238), {226, 137, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1793 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4243), {226, 139, 145, 0}}, #line 401 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4244), {226, 137, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 499 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4247), {197, 139, 0}}, {-1,{0}}, #line 224 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4249), {203, 135, 0}}, {-1,{0}}, #line 167 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4251), {226, 149, 169, 0}}, #line 613 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4252), {226, 170, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1547 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4257), {226, 135, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 174 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4262), {226, 149, 157, 0}}, {-1,{0}}, #line 1804 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4264), {226, 171, 130, 0}}, {-1,{0}}, {-1,{0}}, #line 1409 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4267), {226, 139, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1288 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4272), {226, 128, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1491 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4285), {226, 159, 169, 0}}, {-1,{0}}, #line 824 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4287), {226, 159, 168, 0}}, {-1,{0}}, {-1,{0}}, #line 1315 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4290), {226, 138, 154, 0}}, {-1,{0}}, #line 1515 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4292), {226, 132, 154, 0}}, {-1,{0}}, #line 295 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4294), {226, 136, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1018 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4307), {226, 165, 182, 0}}, #line 194 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4308), {203, 152, 0}}, {-1,{0}}, #line 1077 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4310), {226, 136, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1817 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4315), {226, 164, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1496 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4322), {194, 187, 0}}, {-1,{0}}, #line 830 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4324), {194, 171, 0}}, #line 1815 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4325), {226, 171, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 321 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4329), {226, 139, 147, 0}}, #line 65 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4330), {226, 137, 138, 0}}, #line 1481 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4331), {63, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1305 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4336), {226, 164, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1808 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4340), {226, 138, 131, 0}}, {-1,{0}}, #line 422 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4342), {226, 134, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 452 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4351), {226, 135, 181, 0}}, {-1,{0}}, #line 67 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4353), {39, 0}}, #line 1330 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4354), {195, 146, 0}}, #line 1677 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4355), {226, 136, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1268 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4364), {226, 138, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 966 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4368), {226, 159, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 915 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4377), {226, 170, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1806 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4384), {226, 138, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1126 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4388), {226, 139, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1490 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4396), {226, 166, 179, 0}}, #line 1816 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4397), {226, 171, 150, 0}}, #line 820 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4398), {226, 166, 180, 0}}, {-1,{0}}, {-1,{0}}, #line 1870 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4401), {226, 171, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 501 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4423), {196, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1593 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4429), {226, 137, 147, 0}}, {-1,{0}}, #line 211 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4431), {226, 137, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1009 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4435), {197, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1896 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4439), {197, 166, 0}}, #line 649 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4440), {226, 137, 179, 0}}, {-1,{0}}, {-1,{0}}, #line 105 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4443), {226, 166, 176, 0}}, #line 2109 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4444), {197, 186, 0}}, #line 651 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4445), {226, 170, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 1897 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4448), {197, 167, 0}}, {-1,{0}}, #line 1600 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4450), {226, 159, 173, 0}}, #line 188 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4451), {226, 149, 163, 0}}, #line 962 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4452), {226, 159, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1152 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4456), {226, 169, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1633 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4462), {226, 128, 154, 0}}, {-1,{0}}, #line 1656 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4464), {226, 164, 165, 0}}, #line 956 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4465), {226, 170, 137, 0}}, {-1,{0}}, {-1,{0}}, #line 1809 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4468), {226, 139, 145, 0}}, {-1,{0}}, #line 161 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4470), {226, 149, 164, 0}}, #line 1986 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4471), {207, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 253 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4475), {226, 137, 151, 0}}, {-1,{0}}, #line 2101 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4477), {240, 157, 149, 170}}, {-1,{0}}, #line 1940 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4479), {226, 138, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 825 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4484), {226, 159, 170, 0}}, #line 1100 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4485), {226, 164, 164, 0}}, #line 1673 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4486), {209, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 244 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4492), {240, 157, 148, 160}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 799 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4506), {206, 154, 0}}, #line 943 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4507), {209, 153, 0}}, #line 1045 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4508), {226, 129, 159, 0}}, {-1,{0}}, {-1,{0}}, #line 1810 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4511), {226, 138, 135, 0}}, #line 1811 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4512), {226, 171, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1544 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4517), {194, 174, 0}}, #line 30 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4518), {196, 129, 0}}, #line 908 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4519), {226, 139, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2049 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4524), {226, 132, 152, 0}}, #line 1892 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4525), {208, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1812 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4529), {226, 138, 139, 0}}, #line 1140 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4530), {209, 154, 0}}, #line 2064 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4531), {240, 157, 148, 181}}, {-1,{0}}, #line 1071 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4533), {206, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1297 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4539), {226, 167, 158, 0}}, #line 178 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4540), {226, 149, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2076 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4545), {226, 168, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 886 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4551), {226, 135, 135, 0}}, #line 1786 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4552), {226, 136, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 111 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4559), {226, 132, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 285 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4563), {226, 136, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1286 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4573), {35, 0}}, #line 32 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4574), {38, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 173 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4583), {226, 149, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1176 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4590), {226, 137, 175, 0}}, #line 169 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4591), {226, 138, 158, 0}}, #line 790 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4592), {200, 183, 0}}, {-1,{0}}, #line 1668 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4594), {226, 140, 162, 0}}, {-1,{0}}, #line 447 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4596), {196, 144, 0}}, {-1,{0}}, #line 36 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4598), {226, 136, 167, 0}}, #line 1179 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4599), {226, 137, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1181 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4606), {226, 169, 190, 0}}, {-1,{0}}, #line 1180 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4608), {226, 137, 185, 0}}, #line 1483 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4609), {34, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1178 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4616), {226, 137, 167, 0}}, #line 708 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4617), {226, 128, 144, 0}}, #line 1411 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4618), {226, 132, 143, 0}}, {-1,{0}}, #line 1856 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4620), {226, 137, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1871 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4627), {226, 164, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1008 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4632), {197, 129, 0}}, {-1,{0}}, {-1,{0}}, #line 1680 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4635), {194, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2072 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4639), {226, 139, 187, 0}}, #line 761 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4640), {196, 174, 0}}, {-1,{0}}, {-1,{0}}, #line 455 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4643), {208, 143, 0}}, {-1,{0}}, #line 1333 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4645), {226, 166, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 270 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4652), {226, 167, 130, 0}}, {-1,{0}}, #line 1665 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4654), {226, 156, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1386 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4668), {194, 182, 0}}, {-1,{0}}, {-1,{0}}, #line 76 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4671), {42, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1482 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4678), {226, 137, 159, 0}}, {-1,{0}}, #line 1787 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4680), {226, 136, 145, 0}}, {-1,{0}}, #line 444 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4682), {208, 133, 0}}, {-1,{0}}, #line 498 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4684), {197, 138, 0}}, {-1,{0}}, #line 2122 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4686), {208, 150, 0}}, {-1,{0}}, {-1,{0}}, #line 965 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4689), {226, 159, 181, 0}}, {-1,{0}}, #line 346 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4691), {226, 128, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 437 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4699), {226, 134, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1813 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4706), {226, 171, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1457 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4714), {226, 140, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1311 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4718), {195, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 192 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4729), {226, 149, 160, 0}}, {-1,{0}}, {-1,{0}}, #line 458 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4732), {195, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1807 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4738), {226, 171, 128, 0}}, {-1,{0}}, #line 694 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4740), {226, 134, 169, 0}}, {-1,{0}}, {-1,{0}}, #line 273 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4743), {226, 128, 153, 0}}, {-1,{0}}, {-1,{0}}, #line 1887 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4746), {226, 167, 141, 0}}, #line 405 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4747), {226, 138, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1623 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4751), {226, 139, 138, 0}}, {-1,{0}}, #line 1017 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4753), {226, 139, 137, 0}}, {-1,{0}}, {-1,{0}}, #line 1864 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4756), {226, 164, 168, 0}}, #line 23 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4757), {195, 128, 0}}, {-1,{0}}, {-1,{0}}, #line 75 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4760), {226, 137, 148, 0}}, #line 1492 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4761), {226, 159, 171, 0}}, #line 760 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4762), {209, 145, 0}}, {-1,{0}}, #line 1207 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4764), {226, 170, 175, 0}}, {-1,{0}}, #line 61 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4766), {240, 157, 149, 146}}, {-1,{0}}, #line 251 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4768), {207, 135, 0}}, {-1,{0}}, {-1,{0}}, #line 1479 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4771), {226, 132, 141, 0}}, #line 187 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4772), {226, 149, 162, 0}}, #line 1177 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4773), {226, 137, 177, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2066 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4777), {226, 159, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1361 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4791), {226, 132, 180, 0}}, {-1,{0}}, {-1,{0}}, #line 1620 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4794), {226, 128, 153, 0}}, {-1,{0}}, #line 1006 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4796), {226, 128, 152, 0}}, #line 2103 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4797), {240, 157, 147, 142}}, {-1,{0}}, {-1,{0}}, #line 603 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4800), {196, 161, 0}}, {-1,{0}}, #line 1214 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4802), {226, 139, 162, 0}}, #line 809 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4803), {208, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 202 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4809), {226, 167, 133, 0}}, #line 1213 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4810), {226, 138, 143, 0}}, #line 1672 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4811), {208, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2098 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4821), {208, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 338 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4825), {226, 136, 177, 0}}, {-1,{0}}, {-1,{0}}, #line 1841 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4828), {206, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1842 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4837), {206, 184, 0}}, #line 2070 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4838), {226, 159, 184, 0}}, {-1,{0}}, #line 1216 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4840), {226, 139, 163, 0}}, {-1,{0}}, {-1,{0}}, #line 365 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4843), {226, 166, 177, 0}}, #line 1875 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4844), {226, 150, 181, 0}}, {-1,{0}}, #line 602 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4846), {196, 160, 0}}, {-1,{0}}, #line 1215 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4848), {226, 138, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 8 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4857), {196, 130, 0}}, {-1,{0}}, {-1,{0}}, #line 448 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4860), {196, 145, 0}}, #line 1399 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4861), {226, 128, 177, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1521 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4866), {93, 0}}, {-1,{0}}, #line 851 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4868), {91, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1323 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4872), {226, 166, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1347 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4878), {226, 166, 182, 0}}, {-1,{0}}, #line 2079 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4880), {226, 159, 185, 0}}, {-1,{0}}, #line 1877 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4882), {226, 151, 131, 0}}, #line 1182 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4883), {226, 137, 181, 0}}, #line 279 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4884), {226, 137, 148, 0}}, {-1,{0}}, #line 967 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4886), {226, 159, 184, 0}}, {-1,{0}}, #line 766 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4888), {206, 185, 0}}, {-1,{0}}, #line 276 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4890), {58, 0}}, #line 2118 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4891), {206, 150, 0}}, #line 596 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4892), {196, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 246 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4897), {208, 167, 0}}, {-1,{0}}, {-1,{0}}, #line 2104 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4900), {208, 174, 0}}, #line 1545 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4901), {194, 174, 0}}, #line 1822 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4902), {195, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 456 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4909), {209, 159, 0}}, {-1,{0}}, #line 110 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4911), {206, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 538 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4918), {226, 130, 172, 0}}, {-1,{0}}, {-1,{0}}, #line 874 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4921), {226, 134, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 221 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4924), {226, 133, 133, 0}}, {-1,{0}}, #line 1592 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4926), {203, 154, 0}}, #line 829 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4927), {226, 132, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 391 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4932), {209, 146, 0}}, {-1,{0}}, #line 1355 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4934), {226, 138, 149, 0}}, {-1,{0}}, {-1,{0}}, #line 751 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4937), {226, 132, 164, 0}}, #line 595 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4938), {196, 158, 0}}, {-1,{0}}, #line 1908 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4940), {209, 158, 0}}, #line 537 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4941), {195, 171, 0}}, {-1,{0}}, {-1,{0}}, #line 361 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4944), {194, 176, 0}}, {-1,{0}}, #line 1982 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4946), {195, 188, 0}}, {-1,{0}}, {-1,{0}}, #line 709 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4949), {195, 141, 0}}, #line 1780 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4950), {226, 170, 176, 0}}, {-1,{0}}, #line 811 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4952), {208, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 319 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4961), {226, 137, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1893 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4975), {209, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 241 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4982), {194, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 390 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str4991), {208, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1857 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5009), {226, 137, 133, 0}}, {-1,{0}}, #line 1879 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5011), {226, 137, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 453 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5016), {226, 165, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 879 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5025), {226, 159, 166, 0}}, {-1,{0}}, #line 942 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5027), {208, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 718 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5036), {208, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1878 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5043), {226, 138, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1110 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5049), {226, 137, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1254 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5055), {226, 136, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1099 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5062), {226, 128, 147, 0}}, #line 148 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5063), {226, 139, 136, 0}}, {-1,{0}}, #line 557 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5065), {102, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1907 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5072), {208, 142, 0}}, {-1,{0}}, #line 1999 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5074), {207, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1981 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5078), {195, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2001 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5084), {226, 138, 179, 0}}, #line 2000 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5085), {226, 138, 178, 0}}, #line 74 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5086), {240, 157, 146, 182}}, {-1,{0}}, {-1,{0}}, #line 1775 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5089), {226, 137, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 337 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5093), {226, 136, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1638 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5101), {226, 137, 187, 0}}, {-1,{0}}, #line 559 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5103), {239, 172, 130, 0}}, {-1,{0}}, #line 256 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5105), {226, 138, 155, 0}}, {-1,{0}}, {-1,{0}}, #line 2009 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5108), {226, 138, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1292 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5112), {226, 138, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1803 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5120), {226, 165, 187, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1602 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5124), {226, 159, 167, 0}}, {-1,{0}}, #line 964 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5126), {226, 159, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2007 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5142), {226, 138, 162, 0}}, #line 2107 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5143), {197, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 654 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5151), {62, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 226 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5156), {226, 169, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1776 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5173), {226, 137, 187, 0}}, #line 1310 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5174), {195, 147, 0}}, #line 1874 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5175), {226, 132, 162, 0}}, #line 1139 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5176), {208, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 657 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5181), {226, 139, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2097 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5189), {240, 157, 148, 182}}, {-1,{0}}, {-1,{0}}, #line 284 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5192), {226, 136, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 656 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5197), {226, 137, 171, 0}}, #line 1647 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5198), {226, 170, 182, 0}}, #line 731 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5199), {196, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 261 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5203), {226, 147, 136, 0}}, {-1,{0}}, {-1,{0}}, #line 2095 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5206), {194, 165, 0}}, {-1,{0}}, #line 1843 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5208), {207, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 783 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5211), {195, 175, 0}}, #line 1778 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5212), {226, 137, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 159 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5217), {226, 149, 144, 0}}, #line 1073 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5218), {226, 138, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1577 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5222), {226, 135, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 280 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5227), {226, 137, 148, 0}}, {-1,{0}}, #line 1637 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5229), {226, 170, 188, 0}}, #line 629 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5230), {226, 170, 164, 0}}, #line 719 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5231), {194, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 234 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5234), {226, 169, 140, 0}}, {-1,{0}}, #line 2059 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5236), {226, 139, 130, 0}}, #line 2123 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5237), {208, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 163 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5241), {226, 149, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 911 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5250), {226, 169, 189, 0}}, {-1,{0}}, #line 1957 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5252), {226, 134, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 350 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5257), {203, 157, 0}}, {-1,{0}}, {-1,{0}}, #line 1470 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5260), {226, 128, 136, 0}}, {-1,{0}}, #line 228 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5262), {196, 141, 0}}, {-1,{0}}, #line 1519 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5264), {226, 157, 179, 0}}, {-1,{0}}, #line 849 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5266), {226, 157, 178, 0}}, {-1,{0}}, #line 58 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5268), {196, 132, 0}}, #line 898 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5269), {226, 167, 143, 0}}, {-1,{0}}, {-1,{0}}, #line 615 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5272), {226, 170, 132, 0}}, #line 900 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5273), {226, 138, 180, 0}}, #line 899 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5274), {226, 138, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 290 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5280), {226, 136, 174, 0}}, {-1,{0}}, {-1,{0}}, #line 439 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5283), {226, 164, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1626 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5295), {226, 150, 184, 0}}, {-1,{0}}, #line 1022 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5297), {226, 151, 130, 0}}, {-1,{0}}, {-1,{0}}, #line 1548 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5300), {226, 165, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 878 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5306), {226, 140, 136, 0}}, {-1,{0}}, #line 1979 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5308), {226, 150, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2061 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5314), {226, 139, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 545 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5319), {226, 137, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1528 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5325), {197, 151, 0}}, {-1,{0}}, #line 858 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5327), {196, 188, 0}}, {-1,{0}}, #line 1643 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5329), {197, 159, 0}}, {-1,{0}}, #line 1830 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5331), {197, 162, 0}}, {-1,{0}}, #line 1748 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5333), {226, 152, 133, 0}}, #line 168 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5334), {226, 138, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1831 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5340), {197, 163, 0}}, #line 2117 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5341), {226, 128, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1093 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5350), {197, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1404 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5358), {207, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 711 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5375), {226, 129, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 220 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5384), {226, 169, 128, 0}}, {-1,{0}}, {-1,{0}}, #line 445 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5387), {209, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 248 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5397), {226, 156, 147, 0}}, #line 1381 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5398), {226, 140, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1280 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5405), {226, 139, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1580 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5411), {226, 138, 162, 0}}, #line 1294 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5412), {226, 137, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 892 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5424), {226, 134, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 987 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5431), {226, 151, 138, 0}}, {-1,{0}}, {-1,{0}}, #line 1583 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5434), {226, 167, 144, 0}}, {-1,{0}}, #line 1581 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5436), {226, 165, 155, 0}}, {-1,{0}}, #line 1585 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5438), {226, 138, 181, 0}}, #line 1584 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5439), {226, 138, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 802 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5449), {196, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1642 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5457), {197, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 268 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5468), {226, 168, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 490 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5471), {226, 136, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 22 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5478), {240, 157, 148, 158}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 376 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5482), {203, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 882 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5489), {226, 135, 131, 0}}, {-1,{0}}, {-1,{0}}, #line 881 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5492), {226, 165, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 907 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5501), {226, 170, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 68 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5509), {226, 129, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 208 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5512), {226, 170, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 857 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5524), {196, 187, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 223 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5528), {226, 129, 129, 0}}, {-1,{0}}, #line 91 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5530), {226, 171, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 229 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5543), {195, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 260 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5547), {194, 174, 0}}, #line 880 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5548), {226, 165, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1895 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5552), {209, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 402 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5556), {226, 137, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 242 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5564), {194, 183, 0}}, {-1,{0}}, #line 1281 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5566), {226, 139, 172, 0}}, {-1,{0}}, #line 1056 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5568), {226, 136, 146, 0}}, {-1,{0}}, #line 623 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5570), {226, 132, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 6 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5577), {195, 129, 0}}, #line 653 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5578), {226, 169, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 661 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5583), {226, 165, 184, 0}}, #line 205 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5584), {226, 128, 162, 0}}, {-1,{0}}, {-1,{0}}, #line 423 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5587), {226, 134, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1536 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5593), {226, 128, 157, 0}}, {-1,{0}}, #line 865 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5595), {226, 128, 158, 0}}, {-1,{0}}, {-1,{0}}, #line 755 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5598), {226, 168, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1977 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5602), {197, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 589 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5612), {199, 181, 0}}, {-1,{0}}, #line 1278 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5614), {195, 177, 0}}, #line 20 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5615), {226, 129, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 703 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5618), {196, 166, 0}}, {-1,{0}}, #line 543 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5620), {226, 133, 135, 0}}, #line 1055 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5621), {226, 138, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1587 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5625), {226, 165, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1964 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5630), {226, 134, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2119 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5639), {206, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 373 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5644), {203, 153, 0}}, #line 374 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5645), {203, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1146 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5663), {226, 134, 154, 0}}, #line 691 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5664), {226, 164, 166, 0}}, {-1,{0}}, #line 729 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5666), {226, 132, 169, 0}}, {-1,{0}}, {-1,{0}}, #line 62 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5669), {226, 169, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1092 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5673), {197, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 214 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5678), {226, 169, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1042 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5686), {226, 128, 148, 0}}, {-1,{0}}, {-1,{0}}, #line 554 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5689), {239, 172, 129, 0}}, #line 1648 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5690), {226, 139, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1540 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5699), {226, 132, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 897 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5703), {226, 139, 139, 0}}, #line 77 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5704), {226, 137, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 685 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5718), {226, 128, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 451 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5722), {226, 150, 190, 0}}, {-1,{0}}, #line 1175 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5724), {226, 136, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1639 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5728), {226, 137, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2089 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5733), {208, 175, 0}}, #line 1976 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5734), {197, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1173 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5741), {226, 137, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1848 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5747), {226, 128, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 64 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5754), {226, 169, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 206 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5762), {226, 128, 162, 0}}, {-1,{0}}, {-1,{0}}, #line 272 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5765), {226, 128, 157, 0}}, #line 363 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5766), {206, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 620 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5776), {226, 137, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1378 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5780), {226, 138, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2056 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5799), {226, 137, 128, 0}}, {-1,{0}}, #line 1527 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5801), {197, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 535 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5807), {195, 176, 0}}, #line 1805 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5808), {226, 171, 140, 0}}, {-1,{0}}, {-1,{0}}, #line 84 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5811), {226, 168, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 195 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5817), {203, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 621 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5822), {226, 139, 153, 0}}, {-1,{0}}, #line 706 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5824), {226, 137, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 948 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5837), {226, 135, 154, 0}}, #line 154 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5838), {226, 148, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1782 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5847), {226, 170, 182, 0}}, #line 1971 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5848), {197, 175, 0}}, #line 929 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5849), {226, 169, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1290 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5860), {226, 138, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 669 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5866), {203, 135, 0}}, #line 779 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5867), {196, 169, 0}}, {-1,{0}}, {-1,{0}}, #line 765 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5870), {206, 153, 0}}, {-1,{0}}, #line 759 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5872), {208, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 156 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5884), {226, 149, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1779 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5891), {226, 137, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 883 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5905), {226, 140, 138, 0}}, #line 2041 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5906), {226, 138, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1876 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5923), {226, 150, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 969 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5927), {226, 159, 183, 0}}, #line 1572 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5928), {226, 140, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 434 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5931), {226, 165, 159, 0}}, {-1,{0}}, #line 1480 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5933), {226, 168, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1277 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5937), {195, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 210 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5940), {226, 137, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 668 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5949), {226, 137, 169, 0}}, {-1,{0}}, #line 164 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5951), {226, 148, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 658 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5956), {226, 166, 149, 0}}, {-1,{0}}, {-1,{0}}, #line 1237 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5959), {226, 138, 128, 0}}, {-1,{0}}, {-1,{0}}, #line 1380 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5962), {195, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 611 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5970), {226, 170, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 536 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5976), {195, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1970 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5980), {197, 174, 0}}, {-1,{0}}, #line 1937 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5982), {226, 142, 181, 0}}, #line 1161 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5983), {226, 137, 170, 0}}, #line 872 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5984), {226, 135, 164, 0}}, #line 1095 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str5985), {226, 169, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 78 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6003), {226, 137, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1058 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6023), {226, 168, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 364 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6030), {206, 180, 0}}, {-1,{0}}, #line 678 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6032), {226, 134, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 38 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6038), {226, 169, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 237 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6043), {196, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 225 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6048), {226, 132, 173, 0}}, #line 166 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6049), {226, 149, 168, 0}}, {-1,{0}}, {-1,{0}}, #line 1784 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6052), {226, 137, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 266 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6061), {226, 167, 131, 0}}, #line 1653 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6062), {226, 138, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1318 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6066), {226, 138, 157, 0}}, #line 269 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6067), {226, 171, 175, 0}}, #line 1802 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6068), {226, 171, 151, 0}}, #line 1795 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6069), {226, 171, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1794 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6077), {226, 170, 190, 0}}, {-1,{0}}, #line 83 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6079), {226, 136, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1894 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6084), {208, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 639 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6087), {96, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1004 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6101), {226, 170, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1949 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6106), {226, 135, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 906 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6121), {226, 134, 188, 0}}, #line 416 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6122), {226, 135, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1108 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6129), {226, 128, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 941 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6140), {226, 150, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 267 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6146), {226, 137, 151, 0}}, #line 1293 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6147), {226, 138, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1927 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6151), {226, 150, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 737 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6155), {226, 132, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1586 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6161), {226, 165, 143, 0}}, {-1,{0}}, {-1,{0}}, #line 151 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6164), {226, 149, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 626 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6176), {226, 170, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 782 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6193), {195, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1325 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6203), {197, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1198 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6208), {226, 169, 189, 0}}, {-1,{0}}, #line 153 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6210), {226, 149, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 591 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6215), {206, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1377 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6236), {226, 168, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 968 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6248), {226, 159, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 590 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6261), {206, 147, 0}}, #line 127 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6262), {226, 139, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 160 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6268), {226, 148, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1796 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6283), {226, 171, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 902 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6292), {226, 165, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 614 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6298), {226, 170, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 800 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6304), {206, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1124 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6315), {226, 169, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 665 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6340), {226, 137, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 550 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6351), {239, 172, 128, 0}}, #line 121 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6352), {226, 168, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 808 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6367), {196, 184, 0}}, #line 1797 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6368), {226, 138, 135, 0}}, {-1,{0}}, #line 170 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6370), {226, 138, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 631 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6386), {226, 170, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 427 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6394), {226, 135, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 125 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6403), {226, 168, 132, 0}}, #line 810 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6404), {209, 133, 0}}, {-1,{0}}, #line 355 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6406), {226, 128, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1379 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6418), {195, 150, 0}}, {-1,{0}}, #line 109 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6420), {206, 146, 0}}, #line 1057 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6421), {226, 136, 184, 0}}, #line 1783 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6422), {226, 139, 169, 0}}, {-1,{0}}, #line 310 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6424), {226, 139, 175, 0}}, {-1,{0}}, {-1,{0}}, #line 812 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6427), {209, 156, 0}}, #line 625 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6428), {209, 147, 0}}, {-1,{0}}, #line 1094 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6430), {226, 137, 135, 0}}, #line 2085 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6431), {226, 139, 129, 0}}, #line 98 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6432), {226, 137, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1722 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6439), {226, 138, 145, 0}}, {-1,{0}}, {-1,{0}}, #line 155 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6442), {226, 149, 146, 0}}, {-1,{0}}, {-1,{0}}, #line 970 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6445), {226, 159, 186, 0}}, {-1,{0}}, #line 1721 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6447), {226, 138, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 430 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6451), {226, 165, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 1723 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6454), {226, 138, 143, 0}}, {-1,{0}}, #line 1229 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6456), {226, 136, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1174 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6461), {226, 137, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 150 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6485), {226, 148, 144, 0}}, {-1,{0}}, {-1,{0}}, #line 157 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6488), {226, 149, 148, 0}}, {-1,{0}}, #line 34 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6490), {226, 169, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1591 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6502), {226, 135, 128, 0}}, {-1,{0}}, #line 730 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6504), {196, 178, 0}}, #line 1226 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6505), {226, 137, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 57 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6509), {226, 141, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 52 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6515), {226, 136, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 11 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6521), {226, 136, 191, 0}}, {-1,{0}}, {-1,{0}}, #line 37 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6524), {226, 169, 156, 0}}, {-1,{0}}, #line 1240 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6526), {226, 164, 179, 0}}, #line 2025 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6527), {226, 128, 138, 0}}, {-1,{0}}, #line 1799 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6529), {226, 138, 131, 0}}, {-1,{0}}, #line 152 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6531), {226, 149, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2029 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6535), {226, 138, 130, 0}}, {-1,{0}}, {-1,{0}}, #line 235 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6538), {226, 169, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1987 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6548), {226, 136, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1532 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6552), {209, 128, 0}}, {-1,{0}}, #line 862 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6554), {208, 187, 0}}, {-1,{0}}, #line 1652 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6556), {209, 129, 0}}, {-1,{0}}, #line 1832 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6558), {208, 162, 0}}, #line 2112 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6559), {208, 151, 0}}, #line 468 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6560), {209, 141, 0}}, #line 1537 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6561), {226, 134, 179, 0}}, {-1,{0}}, #line 868 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6563), {226, 134, 178, 0}}, {-1,{0}}, #line 1914 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6565), {209, 131, 0}}, #line 184 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6566), {226, 149, 172, 0}}, #line 1833 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6567), {209, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1098 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6577), {208, 189, 0}}, {-1,{0}}, #line 100 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6579), {208, 177, 0}}, #line 1276 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6580), {226, 137, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 786 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6585), {208, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 288 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6600), {226, 169, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 56 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6607), {195, 133, 0}}, {-1,{0}}, #line 1569 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6609), {226, 165, 157, 0}}, {-1,{0}}, {-1,{0}}, #line 1385 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6612), {226, 143, 156, 0}}, #line 1019 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6613), {226, 169, 187, 0}}, {-1,{0}}, #line 1394 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6615), {208, 191, 0}}, {-1,{0}}, {-1,{0}}, #line 1375 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6618), {195, 181, 0}}, #line 1535 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6619), {226, 128, 157, 0}}, {-1,{0}}, #line 864 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6621), {226, 128, 156, 0}}, {-1,{0}}, #line 2005 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6623), {208, 146, 0}}, {-1,{0}}, {-1,{0}}, #line 215 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6626), {226, 169, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 101 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6646), {226, 128, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 421 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6650), {226, 164, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2006 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6657), {208, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 53 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6665), {226, 138, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 804 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6676), {208, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1040 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6683), {208, 156, 0}}, #line 1651 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6684), {208, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1115 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6691), {10, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 547 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6696), {209, 132, 0}}, #line 1913 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6697), {208, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 183 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6704), {226, 149, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 353 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6715), {208, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 704 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6738), {196, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 861 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6751), {208, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2093 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6762), {208, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1814 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6775), {226, 171, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1164 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6789), {194, 160, 0}}, #line 1382 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6790), {226, 128, 190, 0}}, #line 1724 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6791), {226, 138, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 624 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6797), {208, 131, 0}}, {-1,{0}}, {-1,{0}}, #line 1383 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6800), {226, 143, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 512 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6806), {226, 137, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1384 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6819), {226, 142, 180, 0}}, {-1,{0}}, #line 81 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6821), {195, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 15 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6829), {194, 180, 0}}, #line 715 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6830), {208, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 778 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6849), {196, 168, 0}}, #line 689 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6850), {226, 132, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1344 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6854), {207, 137, 0}}, #line 213 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6855), {196, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1645 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6861), {197, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 464 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6865), {195, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1912 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6870), {195, 187, 0}}, {-1,{0}}, #line 645 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6872), {226, 169, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 784 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6890), {196, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1291 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6895), {226, 138, 173, 0}}, #line 2043 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6896), {197, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1097 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6900), {208, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1579 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6921), {226, 134, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 924 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6942), {226, 137, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1010 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6958), {226, 170, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 26 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6963), {226, 132, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 354 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6979), {208, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1644 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6989), {197, 156, 0}}, {-1,{0}}, #line 919 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str6991), {226, 170, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 717 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7000), {208, 149, 0}}, #line 985 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7001), {226, 134, 152, 0}}, #line 1911 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7002), {195, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 24 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7021), {195, 160, 0}}, {-1,{0}}, #line 1059 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7023), {226, 136, 147, 0}}, #line 126 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7024), {226, 139, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1531 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7028), {208, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1801 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7034), {226, 159, 137, 0}}, {-1,{0}}, {-1,{0}}, #line 494 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7037), {226, 150, 171, 0}}, {-1,{0}}, #line 162 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7039), {226, 149, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1435 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7047), {226, 170, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 54 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7066), {226, 166, 157, 0}}, #line 2091 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7067), {197, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1752 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7071), {226, 138, 130, 0}}, {-1,{0}}, {-1,{0}}, #line 1374 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7074), {195, 149, 0}}, #line 231 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7075), {196, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 546 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7085), {208, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 286 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7090), {226, 132, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1762 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7096), {226, 165, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 757 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7115), {226, 129, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 175 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7120), {226, 148, 148, 0}}, #line 9 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7121), {196, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1279 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7127), {226, 137, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 713 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7135), {195, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2062 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7142), {226, 150, 189, 0}}, #line 252 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7143), {203, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 662 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7168), {226, 139, 151, 0}}, {-1,{0}}, {-1,{0}}, #line 610 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7171), {226, 169, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1282 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7183), {226, 139, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 313 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7198), {226, 139, 158, 0}}, #line 1753 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7199), {226, 139, 144, 0}}, {-1,{0}}, #line 1041 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7201), {208, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1859 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7212), {226, 168, 177, 0}}, {-1,{0}}, #line 690 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7214), {226, 164, 165, 0}}, {-1,{0}}, {-1,{0}}, #line 1682 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7217), {207, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 324 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7224), {226, 169, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1372 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7230), {195, 184, 0}}, #line 457 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7231), {226, 159, 191, 0}}, {-1,{0}}, {-1,{0}}, #line 891 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7234), {226, 135, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1576 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7245), {226, 135, 140, 0}}, {-1,{0}}, #line 803 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7247), {196, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1758 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7256), {226, 171, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 332 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7260), {194, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 896 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7269), {226, 165, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 122 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7274), {226, 152, 133, 0}}, {-1,{0}}, {-1,{0}}, #line 320 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7277), {226, 136, 170, 0}}, #line 973 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7278), {226, 159, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 597 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7294), {196, 162, 0}}, {-1,{0}}, #line 1439 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7296), {226, 170, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2113 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7307), {208, 183, 0}}, {-1,{0}}, #line 1412 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7309), {226, 132, 142, 0}}, #line 1343 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7310), {206, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1771 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7317), {226, 171, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1533 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7325), {226, 164, 183, 0}}, #line 325 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7326), {226, 136, 170, 0}}, #line 863 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7327), {226, 164, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1763 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7332), {226, 138, 130, 0}}, #line 1219 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7333), {226, 138, 129, 0}}, #line 876 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7334), {226, 135, 134, 0}}, {-1,{0}}, {-1,{0}}, #line 2044 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7337), {197, 181, 0}}, #line 1560 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7338), {226, 159, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1283 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7344), {226, 139, 173, 0}}, #line 1681 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7345), {206, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1222 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7350), {226, 137, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 372 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7364), {194, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1760 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7376), {226, 138, 138, 0}}, {-1,{0}}, #line 1456 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7378), {226, 136, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 258 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7385), {226, 138, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1772 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7389), {226, 171, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 297 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7397), {194, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 533 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7403), {206, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 51 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7409), {226, 136, 161, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1083 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7434), {226, 153, 174, 0}}, {-1,{0}}, #line 1798 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7436), {226, 171, 132, 0}}, #line 1084 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7437), {226, 132, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1880 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7443), {226, 150, 185, 0}}, {-1,{0}}, #line 375 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7445), {96, 0}}, #line 172 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7446), {226, 149, 155, 0}}, #line 287 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7447), {226, 137, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1835 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7451), {226, 140, 149, 0}}, {-1,{0}}, {-1,{0}}, #line 281 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7454), {44, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1764 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7460), {226, 139, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1221 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7475), {226, 139, 161, 0}}, #line 663 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7476), {226, 139, 155, 0}}, #line 79 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7477), {195, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 326 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7484), {226, 134, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 312 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7491), {226, 164, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 311 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7495), {226, 164, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1765 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7503), {226, 138, 134, 0}}, #line 1766 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7504), {226, 171, 133, 0}}, #line 1578 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7505), {226, 134, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 318 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7520), {226, 169, 134, 0}}, #line 1768 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7521), {226, 138, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 59 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7532), {196, 133, 0}}, #line 1190 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7533), {226, 139, 182, 0}}, #line 1582 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7534), {226, 139, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2088 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7552), {195, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1147 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7563), {226, 135, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1317 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7581), {208, 190, 0}}, #line 240 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7582), {226, 166, 178, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 467 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7595), {208, 173, 0}}, {-1,{0}}, {-1,{0}}, #line 322 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7598), {226, 169, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1881 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7604), {226, 138, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 888 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7615), {226, 134, 148, 0}}, {-1,{0}}, {-1,{0}}, #line 1774 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7618), {226, 137, 187, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 425 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7631), {226, 135, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1324 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7641), {197, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 247 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7648), {209, 135, 0}}, #line 664 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7649), {226, 170, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 42 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7655), {226, 136, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 12 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7662), {226, 136, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1597 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7668), {226, 142, 177, 0}}, {-1,{0}}, #line 953 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7670), {226, 142, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1109 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7674), {226, 128, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 1082 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7677), {226, 137, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1371 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7686), {195, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1769 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7698), {226, 171, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 71 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7723), {195, 133, 0}}, #line 176 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7724), {226, 149, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1761 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7730), {226, 170, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2086 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7742), {226, 139, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 171 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7767), {226, 148, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 189 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7778), {226, 148, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 705 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7800), {226, 137, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 714 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7812), {208, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 70 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7828), {226, 137, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 7 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7841), {195, 161, 0}}, #line 66 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7842), {226, 137, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1951 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7859), {226, 134, 149, 0}}, {-1,{0}}, #line 1113 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7861), {226, 137, 171, 0}}, {-1,{0}}, #line 787 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7863), {208, 185, 0}}, {-1,{0}}, {-1,{0}}, #line 666 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7866), {226, 137, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 179 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7876), {226, 148, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1314 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7886), {195, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 463 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7900), {195, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1205 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str7987), {226, 139, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 124 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8006), {226, 150, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 342 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8032), {226, 132, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1316 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8037), {208, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 681 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8042), {196, 164, 0}}, #line 1590 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8043), {226, 165, 147, 0}}, #line 18 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8044), {195, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 556 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8063), {226, 150, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 622 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8084), {226, 139, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 99 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8088), {208, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1426 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8099), {226, 132, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 186 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8104), {226, 149, 161, 0}}, {-1,{0}}, {-1,{0}}, #line 1392 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8107), {226, 136, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 712 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8117), {195, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 315 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8129), {226, 134, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 158 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8135), {226, 148, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 39 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8142), {226, 169, 154, 0}}, {-1,{0}}, #line 1788 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8144), {226, 153, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1568 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8148), {226, 159, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 785 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8168), {196, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1935 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8174), {95, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1563 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8241), {226, 134, 146, 0}}, #line 257 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8242), {226, 138, 154, 0}}, #line 27 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8243), {206, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 885 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8251), {226, 134, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 316 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8258), {226, 164, 189, 0}}, {-1,{0}}, #line 1565 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8260), {226, 135, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1994 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8281), {207, 130, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1287 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8300), {226, 132, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 551 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8310), {239, 172, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 984 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8326), {226, 134, 153, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 542 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8340), {226, 132, 176, 0}}, {-1,{0}}, #line 1313 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8342), {195, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2090 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8351), {209, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 823 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8375), {206, 187, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1220 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8381), {226, 170, 176, 0}}, #line 190 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8382), {226, 149, 158, 0}}, {-1,{0}}, #line 123 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8384), {226, 150, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 40 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8391), {226, 136, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2083 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8404), {226, 168, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1074 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8424), {226, 136, 135, 0}}, #line 185 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8425), {226, 148, 164, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 532 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8438), {206, 151, 0}}, {-1,{0}}, #line 16 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8440), {208, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 805 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8474), {208, 186, 0}}, #line 601 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8475), {208, 179, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 893 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8485), {226, 165, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 230 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8491), {195, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 90 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8495), {226, 136, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 702 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8506), {226, 132, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1393 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8515), {208, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 600 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8521), {208, 147, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 659 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8534), {226, 169, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 822 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8572), {206, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1321 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8627), {226, 168, 184, 0}}, {-1,{0}}, #line 884 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8629), {226, 134, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 971 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8672), {226, 159, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 797 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8677), {208, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 866 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8687), {226, 165, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2084 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8700), {226, 150, 179, 0}}, #line 1245 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8701), {226, 135, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 544 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8725), {226, 133, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1244 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8735), {226, 134, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 13 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8745), {195, 130, 0}}, #line 1163 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8746), {226, 129, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 599 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8780), {196, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 41 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8784), {226, 166, 164, 0}}, #line 327 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8785), {226, 164, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1670 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8791), {208, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2106 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8796), {195, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1759 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8800), {226, 171, 139, 0}}, {-1,{0}}, {-1,{0}}, #line 359 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8803), {226, 164, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1628 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8810), {226, 167, 180, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 598 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8826), {196, 156, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 795 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8843), {208, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 652 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8879), {226, 170, 167, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 781 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8922), {209, 150, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1950 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8956), {226, 134, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 330 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8962), {226, 139, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 549 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8972), {239, 172, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2099 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str8992), {209, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 389 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9015), {226, 139, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 660 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9026), {226, 170, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1754 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9069), {226, 170, 189, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 890 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9079), {226, 135, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 82 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9085), {195, 164, 0}}, {-1,{0}}, {-1,{0}}, #line 1952 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9088), {226, 135, 149, 0}}, {-1,{0}}, #line 1575 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9090), {226, 135, 132, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 436 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9151), {226, 135, 129, 0}}, {-1,{0}}, {-1,{0}}, #line 435 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9154), {226, 165, 151, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 682 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9162), {196, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1613 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9186), {226, 135, 155, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 972 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9217), {226, 159, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 323 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9239), {226, 138, 141, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 10 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9249), {226, 136, 190, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 695 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9268), {226, 134, 170, 0}}, {-1,{0}}, {-1,{0}}, #line 1107 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9271), {226, 128, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1755 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9275), {226, 171, 133, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1900 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9307), {226, 134, 160, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 429 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9320), {226, 135, 130, 0}}, #line 428 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9321), {226, 135, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 19 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9326), {195, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1534 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9330), {226, 165, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 331 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9349), {226, 139, 143, 0}}, {-1,{0}}, #line 707 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9351), {226, 129, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1756 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9360), {226, 138, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 974 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9414), {226, 159, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 239 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9484), {194, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1188 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9505), {226, 136, 137, 0}}, #line 1777 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9506), {226, 170, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 887 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9554), {226, 134, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1749 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9580), {207, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 31 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9627), {226, 168, 191, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 80 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9741), {195, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1567 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9747), {226, 140, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 889 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9751), {226, 135, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1770 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9767), {226, 171, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2022 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9788), {124, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1589 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9801), {226, 134, 190, 0}}, {-1,{0}}, {-1,{0}}, #line 1588 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9804), {226, 165, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1571 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9829), {226, 135, 130, 0}}, {-1,{0}}, {-1,{0}}, #line 1570 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9832), {226, 165, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 25 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9836), {226, 132, 181, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 255 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9852), {226, 134, 187, 0}}, #line 254 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9853), {226, 134, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 780 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9904), {208, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1376 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9936), {226, 168, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 753 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9944), {226, 138, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1845 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9952), {226, 137, 136, 0}}, {-1,{0}}, {-1,{0}}, #line 798 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9955), {209, 148, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1203 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9959), {226, 136, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1443 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9963), {226, 170, 185, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 335 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9983), {226, 139, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 72 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str9987), {195, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 232 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10023), {196, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1562 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10029), {226, 134, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 752 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10061), {226, 136, 171, 0}}, #line 2060 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10062), {226, 151, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 796 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10121), {209, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 249 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10206), {226, 156, 147, 0}}, {-1,{0}}, #line 2024 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10208), {226, 137, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 182 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10219), {226, 149, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1210 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10240), {226, 167, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1212 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10244), {226, 139, 173, 0}}, #line 1211 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10245), {226, 139, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 905 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10278), {226, 165, 146, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 181 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10357), {226, 148, 188, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 149 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10395), {226, 167, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2094 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10415), {209, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1757 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10428), {226, 171, 131, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1706 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10445), {208, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1564 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10505), {226, 135, 146, 0}}, {-1,{0}}, #line 28 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10507), {206, 177, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1671 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10528), {209, 137, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1707 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10584), {209, 140, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 17 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10704), {208, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2092 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10720), {197, 183, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 116 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10791), {226, 151, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 735 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10808), {226, 133, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 69 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10847), {226, 137, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1800 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10851), {226, 138, 135, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2042 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10879), {226, 166, 154, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 314 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10888), {226, 139, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1938 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str10947), {226, 143, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 14 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11009), {195, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1773 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11029), {226, 170, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1039 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11047), {226, 168, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 47 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11146), {226, 166, 172, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 44 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11165), {226, 166, 169, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 48 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11282), {226, 166, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 55 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11366), {226, 136, 162, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1025 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11527), {226, 165, 166, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 46 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11565), {226, 166, 171, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1899 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11664), {226, 134, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 339 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11720), {226, 140, 173, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1750 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11791), {207, 149, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1072 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11840), {226, 138, 184, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1561 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str11918), {226, 135, 165, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 867 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12012), {226, 165, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 871 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12103), {226, 159, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1629 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12170), {226, 165, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 328 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12202), {226, 139, 158, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2105 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12206), {209, 142, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1024 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12288), {226, 165, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 674 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12413), {209, 138, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1573 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12461), {226, 135, 129, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1574 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12497), {226, 135, 128, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 673 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12502), {208, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1767 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12651), {226, 138, 134, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 384 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12809), {207, 157, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1917 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12892), {197, 177, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1785 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12985), {226, 136, 139, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 336 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str12991), {226, 139, 143, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1916 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13024), {197, 176, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 49 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13061), {226, 166, 174, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 50 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13443), {226, 166, 175, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2021 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13643), {226, 136, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 2023 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13659), {226, 157, 152, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1566 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13709), {226, 134, 163, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1320 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13908), {197, 145, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1781 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str13945), {226, 170, 186, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 45 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str14304), {226, 166, 170, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 1319 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str14364), {197, 144, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 317 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str14620), {226, 169, 136, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 43 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str15290), {226, 166, 168, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 329 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str15360), {226, 139, 159, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 333 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str15729), {226, 134, 182, 0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, {-1,{0}}, #line 334 "src/html_unescape.gperf" {offsetof(struct entity_pool_t, entity_pool_str16000), {226, 134, 183, 0}} }; if (len <= MAX_WORD_LENGTH && len >= MIN_WORD_LENGTH) { unsigned int key = hash_entity (str, len); if (key <= MAX_HASH_VALUE) if (len == lengthtable[key]) { register const char *s = wordlist[key].entity + entity_pool; if (*str == *s && !memcmp (str + 1, s + 1, len - 1)) return &wordlist[key]; } } return 0; } ������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/iterator.h��������������������������������������������������������������������0000644�0000000�0000000�00000000560�13442034251�014657� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_ITERATOR_H #define CMARK_ITERATOR_H #ifdef __cplusplus extern "C" { #endif #include "cmark-gfm.h" #include "memory.h" typedef struct { cmark_event_type ev_type; cmark_node *node; } cmark_iter_state; struct cmark_iter { cmark_mem *mem; cmark_node *root; cmark_iter_state cur; cmark_iter_state next; }; #ifdef __cplusplus } #endif #endif ������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/node.h������������������������������������������������������������������������0000644�0000000�0000000�00000004571�13442034251�013761� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_NODE_H #define CMARK_NODE_H #ifdef __cplusplus extern "C" { #endif #include <stdio.h> #include <stdint.h> #include "cmark-gfm.h" #include "cmark-gfm-extension_api.h" #include "buffer.h" #include "chunk.h" typedef struct { cmark_list_type list_type; int marker_offset; int padding; int start; cmark_delim_type delimiter; unsigned char bullet_char; bool tight; } cmark_list; typedef struct { cmark_chunk info; cmark_chunk literal; uint8_t fence_length; uint8_t fence_offset; unsigned char fence_char; int8_t fenced; } cmark_code; typedef struct { int level; bool setext; } cmark_heading; typedef struct { cmark_chunk url; cmark_chunk title; } cmark_link; typedef struct { cmark_chunk on_enter; cmark_chunk on_exit; } cmark_custom; enum cmark_node__internal_flags { CMARK_NODE__OPEN = (1 << 0), CMARK_NODE__LAST_LINE_BLANK = (1 << 1), }; struct cmark_node { cmark_strbuf content; struct cmark_node *next; struct cmark_node *prev; struct cmark_node *parent; struct cmark_node *first_child; struct cmark_node *last_child; void *user_data; cmark_free_func user_data_free_func; int start_line; int start_column; int end_line; int end_column; int internal_offset; uint16_t type; uint16_t flags; cmark_syntax_extension *extension; union { cmark_chunk literal; cmark_list list; cmark_code code; cmark_heading heading; cmark_link link; cmark_custom custom; int html_block_type; void *opaque; } as; }; static CMARK_INLINE cmark_mem *cmark_node_mem(cmark_node *node) { return node->content.mem; } CMARK_GFM_EXPORT int cmark_node_check(cmark_node *node, FILE *out); static CMARK_INLINE bool CMARK_NODE_TYPE_BLOCK_P(cmark_node_type node_type) { return (node_type & CMARK_NODE_TYPE_MASK) == CMARK_NODE_TYPE_BLOCK; } static CMARK_INLINE bool CMARK_NODE_BLOCK_P(cmark_node *node) { return node != NULL && CMARK_NODE_TYPE_BLOCK_P((cmark_node_type) node->type); } static CMARK_INLINE bool CMARK_NODE_TYPE_INLINE_P(cmark_node_type node_type) { return (node_type & CMARK_NODE_TYPE_MASK) == CMARK_NODE_TYPE_INLINE; } static CMARK_INLINE bool CMARK_NODE_INLINE_P(cmark_node *node) { return node != NULL && CMARK_NODE_TYPE_INLINE_P((cmark_node_type) node->type); } CMARK_GFM_EXPORT bool cmark_node_can_contain_type(cmark_node *node, cmark_node_type child_type); #ifdef __cplusplus } #endif #endif ���������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/buffer.h����������������������������������������������������������������������0000644�0000000�0000000�00000005302�13442034251�014276� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_BUFFER_H #define CMARK_BUFFER_H #include <stddef.h> #include <stdarg.h> #include <string.h> #include <limits.h> #include <stdint.h> #include "config.h" #include "cmark-gfm.h" #ifdef __cplusplus extern "C" { #endif typedef struct { cmark_mem *mem; unsigned char *ptr; bufsize_t asize, size; } cmark_strbuf; extern unsigned char cmark_strbuf__initbuf[]; #define CMARK_BUF_INIT(mem) \ { mem, cmark_strbuf__initbuf, 0, 0 } /** * Initialize a cmark_strbuf structure. * * For the cases where CMARK_BUF_INIT cannot be used to do static * initialization. */ CMARK_GFM_EXPORT void cmark_strbuf_init(cmark_mem *mem, cmark_strbuf *buf, bufsize_t initial_size); /** * Grow the buffer to hold at least `target_size` bytes. */ CMARK_GFM_EXPORT void cmark_strbuf_grow(cmark_strbuf *buf, bufsize_t target_size); CMARK_GFM_EXPORT void cmark_strbuf_free(cmark_strbuf *buf); CMARK_GFM_EXPORT void cmark_strbuf_swap(cmark_strbuf *buf_a, cmark_strbuf *buf_b); CMARK_GFM_EXPORT bufsize_t cmark_strbuf_len(const cmark_strbuf *buf); CMARK_GFM_EXPORT int cmark_strbuf_cmp(const cmark_strbuf *a, const cmark_strbuf *b); CMARK_GFM_EXPORT unsigned char *cmark_strbuf_detach(cmark_strbuf *buf); CMARK_GFM_EXPORT void cmark_strbuf_copy_cstr(char *data, bufsize_t datasize, const cmark_strbuf *buf); static CMARK_INLINE const char *cmark_strbuf_cstr(const cmark_strbuf *buf) { return (char *)buf->ptr; } #define cmark_strbuf_at(buf, n) ((buf)->ptr[n]) CMARK_GFM_EXPORT void cmark_strbuf_set(cmark_strbuf *buf, const unsigned char *data, bufsize_t len); CMARK_GFM_EXPORT void cmark_strbuf_sets(cmark_strbuf *buf, const char *string); CMARK_GFM_EXPORT void cmark_strbuf_putc(cmark_strbuf *buf, int c); CMARK_GFM_EXPORT void cmark_strbuf_put(cmark_strbuf *buf, const unsigned char *data, bufsize_t len); CMARK_GFM_EXPORT void cmark_strbuf_puts(cmark_strbuf *buf, const char *string); CMARK_GFM_EXPORT void cmark_strbuf_clear(cmark_strbuf *buf); CMARK_GFM_EXPORT bufsize_t cmark_strbuf_strchr(const cmark_strbuf *buf, int c, bufsize_t pos); CMARK_GFM_EXPORT bufsize_t cmark_strbuf_strrchr(const cmark_strbuf *buf, int c, bufsize_t pos); CMARK_GFM_EXPORT void cmark_strbuf_drop(cmark_strbuf *buf, bufsize_t n); CMARK_GFM_EXPORT void cmark_strbuf_truncate(cmark_strbuf *buf, bufsize_t len); CMARK_GFM_EXPORT void cmark_strbuf_rtrim(cmark_strbuf *buf); CMARK_GFM_EXPORT void cmark_strbuf_trim(cmark_strbuf *buf); CMARK_GFM_EXPORT void cmark_strbuf_normalize_whitespace(cmark_strbuf *s); CMARK_GFM_EXPORT void cmark_strbuf_unescape(cmark_strbuf *s); #ifdef __cplusplus } #endif #endif ������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/render.h����������������������������������������������������������������������0000644�0000000�0000000�00000003235�13442034251�014307� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_RENDER_H #define CMARK_RENDER_H #ifdef __cplusplus extern "C" { #endif #include <stdlib.h> #include "buffer.h" #include "chunk.h" #include "memory.h" typedef enum { LITERAL, NORMAL, TITLE, URL } cmark_escaping; struct cmark_renderer { cmark_mem *mem; cmark_strbuf *buffer; cmark_strbuf *prefix; int column; int width; int need_cr; bufsize_t last_breakable; bool begin_line; bool begin_content; bool no_linebreaks; bool in_tight_list_item; void (*outc)(struct cmark_renderer *, cmark_node *, cmark_escaping, int32_t, unsigned char); void (*cr)(struct cmark_renderer *); void (*blankline)(struct cmark_renderer *); void (*out)(struct cmark_renderer *, cmark_node *, const char *, bool, cmark_escaping); unsigned int footnote_ix; }; typedef struct cmark_renderer cmark_renderer; struct cmark_html_renderer { cmark_strbuf *html; cmark_node *plain; cmark_llist *filter_extensions; unsigned int footnote_ix; unsigned int written_footnote_ix; void *opaque; }; typedef struct cmark_html_renderer cmark_html_renderer; void cmark_render_ascii(cmark_renderer *renderer, const char *s); void cmark_render_code_point(cmark_renderer *renderer, uint32_t c); char *cmark_render(cmark_mem *mem, cmark_node *root, int options, int width, void (*outc)(cmark_renderer *, cmark_node *, cmark_escaping, int32_t, unsigned char), int (*render_node)(cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options)); #ifdef __cplusplus } #endif #endif �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/cmark_ctype.h�����������������������������������������������������������������0000644�0000000�0000000�00000001013�13442034251�015321� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_CMARK_CTYPE_H #define CMARK_CMARK_CTYPE_H #ifdef __cplusplus extern "C" { #endif #include "cmark-gfm_export.h" /** Locale-independent versions of functions from ctype.h. * We want cmark to behave the same no matter what the system locale. */ CMARK_GFM_EXPORT int cmark_isspace(char c); CMARK_GFM_EXPORT int cmark_ispunct(char c); CMARK_GFM_EXPORT int cmark_isalnum(char c); CMARK_GFM_EXPORT int cmark_isdigit(char c); CMARK_GFM_EXPORT int cmark_isalpha(char c); #ifdef __cplusplus } #endif #endif ���������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/config.h����������������������������������������������������������������������0000644�0000000�0000000�00000002561�13442034251�014276� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_CONFIG_H #define CMARK_CONFIG_H #ifdef __cplusplus extern "C" { #endif #define HAVE_STDBOOL_H #ifdef HAVE_STDBOOL_H #include <stdbool.h> #elif !defined(__cplusplus) typedef char bool; #endif #define HAVE___BUILTIN_EXPECT #define HAVE___ATTRIBUTE__ #ifdef HAVE___ATTRIBUTE__ #define CMARK_ATTRIBUTE(list) __attribute__ (list) #else #define CMARK_ATTRIBUTE(list) #endif #ifndef CMARK_INLINE #if defined(_MSC_VER) && !defined(__cplusplus) #define CMARK_INLINE __inline #else #define CMARK_INLINE inline #endif #endif /* snprintf and vsnprintf fallbacks for MSVC before 2015, due to Valentin Milea http://stackoverflow.com/questions/2915672/ */ #if defined(_MSC_VER) && _MSC_VER < 1900 #include <stdio.h> #include <stdarg.h> #define snprintf c99_snprintf #define vsnprintf c99_vsnprintf CMARK_INLINE int c99_vsnprintf(char *outBuf, size_t size, const char *format, va_list ap) { int count = -1; if (size != 0) count = _vsnprintf_s(outBuf, size, _TRUNCATE, format, ap); if (count == -1) count = _vscprintf(format, ap); return count; } CMARK_INLINE int c99_snprintf(char *outBuf, size_t size, const char *format, ...) { int count; va_list ap; va_start(ap, format); count = c99_vsnprintf(outBuf, size, format, ap); va_end(ap); return count; } #endif #ifdef __cplusplus } #endif #endif �����������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/scanners.h��������������������������������������������������������������������0000644�0000000�0000000�00000006121�13442034251�014641� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_SCANNERS_H #define CMARK_SCANNERS_H #include "cmark-gfm.h" #include "chunk.h" #ifdef __cplusplus extern "C" { #endif bufsize_t _scan_at(bufsize_t (*scanner)(const unsigned char *), cmark_chunk *c, bufsize_t offset); bufsize_t _scan_scheme(const unsigned char *p); bufsize_t _scan_autolink_uri(const unsigned char *p); bufsize_t _scan_autolink_email(const unsigned char *p); bufsize_t _scan_html_tag(const unsigned char *p); bufsize_t _scan_liberal_html_tag(const unsigned char *p); bufsize_t _scan_html_block_start(const unsigned char *p); bufsize_t _scan_html_block_start_7(const unsigned char *p); bufsize_t _scan_html_block_end_1(const unsigned char *p); bufsize_t _scan_html_block_end_2(const unsigned char *p); bufsize_t _scan_html_block_end_3(const unsigned char *p); bufsize_t _scan_html_block_end_4(const unsigned char *p); bufsize_t _scan_html_block_end_5(const unsigned char *p); bufsize_t _scan_link_title(const unsigned char *p); bufsize_t _scan_spacechars(const unsigned char *p); bufsize_t _scan_atx_heading_start(const unsigned char *p); bufsize_t _scan_setext_heading_line(const unsigned char *p); bufsize_t _scan_thematic_break(const unsigned char *p); bufsize_t _scan_open_code_fence(const unsigned char *p); bufsize_t _scan_close_code_fence(const unsigned char *p); bufsize_t _scan_entity(const unsigned char *p); bufsize_t _scan_dangerous_url(const unsigned char *p); bufsize_t _scan_footnote_definition(const unsigned char *p); #define scan_scheme(c, n) _scan_at(&_scan_scheme, c, n) #define scan_autolink_uri(c, n) _scan_at(&_scan_autolink_uri, c, n) #define scan_autolink_email(c, n) _scan_at(&_scan_autolink_email, c, n) #define scan_html_tag(c, n) _scan_at(&_scan_html_tag, c, n) #define scan_liberal_html_tag(c, n) _scan_at(&_scan_liberal_html_tag, c, n) #define scan_html_block_start(c, n) _scan_at(&_scan_html_block_start, c, n) #define scan_html_block_start_7(c, n) _scan_at(&_scan_html_block_start_7, c, n) #define scan_html_block_end_1(c, n) _scan_at(&_scan_html_block_end_1, c, n) #define scan_html_block_end_2(c, n) _scan_at(&_scan_html_block_end_2, c, n) #define scan_html_block_end_3(c, n) _scan_at(&_scan_html_block_end_3, c, n) #define scan_html_block_end_4(c, n) _scan_at(&_scan_html_block_end_4, c, n) #define scan_html_block_end_5(c, n) _scan_at(&_scan_html_block_end_5, c, n) #define scan_link_title(c, n) _scan_at(&_scan_link_title, c, n) #define scan_spacechars(c, n) _scan_at(&_scan_spacechars, c, n) #define scan_atx_heading_start(c, n) _scan_at(&_scan_atx_heading_start, c, n) #define scan_setext_heading_line(c, n) \ _scan_at(&_scan_setext_heading_line, c, n) #define scan_thematic_break(c, n) _scan_at(&_scan_thematic_break, c, n) #define scan_open_code_fence(c, n) _scan_at(&_scan_open_code_fence, c, n) #define scan_close_code_fence(c, n) _scan_at(&_scan_close_code_fence, c, n) #define scan_entity(c, n) _scan_at(&_scan_entity, c, n) #define scan_dangerous_url(c, n) _scan_at(&_scan_dangerous_url, c, n) #define scan_footnote_definition(c, n) _scan_at(&_scan_footnote_definition, c, n) #ifdef __cplusplus } #endif #endif �����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/case_fold_switch.inc����������������������������������������������������������0000644�0000000�0000000�00000250127�13336672517�016675� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������ switch (c) { case 0x0041: bufpush(0x0061); break; case 0x0042: bufpush(0x0062); break; case 0x0043: bufpush(0x0063); break; case 0x0044: bufpush(0x0064); break; case 0x0045: bufpush(0x0065); break; case 0x0046: bufpush(0x0066); break; case 0x0047: bufpush(0x0067); break; case 0x0048: bufpush(0x0068); break; case 0x0049: bufpush(0x0069); break; case 0x004A: bufpush(0x006A); break; case 0x004B: bufpush(0x006B); break; case 0x004C: bufpush(0x006C); break; case 0x004D: bufpush(0x006D); break; case 0x004E: bufpush(0x006E); break; case 0x004F: bufpush(0x006F); break; case 0x0050: bufpush(0x0070); break; case 0x0051: bufpush(0x0071); break; case 0x0052: bufpush(0x0072); break; case 0x0053: bufpush(0x0073); break; case 0x0054: bufpush(0x0074); break; case 0x0055: bufpush(0x0075); break; case 0x0056: bufpush(0x0076); break; case 0x0057: bufpush(0x0077); break; case 0x0058: bufpush(0x0078); break; case 0x0059: bufpush(0x0079); break; case 0x005A: bufpush(0x007A); break; case 0x00B5: bufpush(0x03BC); break; case 0x00C0: bufpush(0x00E0); break; case 0x00C1: bufpush(0x00E1); break; case 0x00C2: bufpush(0x00E2); break; case 0x00C3: bufpush(0x00E3); break; case 0x00C4: bufpush(0x00E4); break; case 0x00C5: bufpush(0x00E5); break; case 0x00C6: bufpush(0x00E6); break; case 0x00C7: bufpush(0x00E7); break; case 0x00C8: bufpush(0x00E8); break; case 0x00C9: bufpush(0x00E9); break; case 0x00CA: bufpush(0x00EA); break; case 0x00CB: bufpush(0x00EB); break; case 0x00CC: bufpush(0x00EC); break; case 0x00CD: bufpush(0x00ED); break; case 0x00CE: bufpush(0x00EE); break; case 0x00CF: bufpush(0x00EF); break; case 0x00D0: bufpush(0x00F0); break; case 0x00D1: bufpush(0x00F1); break; case 0x00D2: bufpush(0x00F2); break; case 0x00D3: bufpush(0x00F3); break; case 0x00D4: bufpush(0x00F4); break; case 0x00D5: bufpush(0x00F5); break; case 0x00D6: bufpush(0x00F6); break; case 0x00D8: bufpush(0x00F8); break; case 0x00D9: bufpush(0x00F9); break; case 0x00DA: bufpush(0x00FA); break; case 0x00DB: bufpush(0x00FB); break; case 0x00DC: bufpush(0x00FC); break; case 0x00DD: bufpush(0x00FD); break; case 0x00DE: bufpush(0x00FE); break; case 0x00DF: bufpush(0x0073); bufpush(0x0073); break; case 0x0100: bufpush(0x0101); break; case 0x0102: bufpush(0x0103); break; case 0x0104: bufpush(0x0105); break; case 0x0106: bufpush(0x0107); break; case 0x0108: bufpush(0x0109); break; case 0x010A: bufpush(0x010B); break; case 0x010C: bufpush(0x010D); break; case 0x010E: bufpush(0x010F); break; case 0x0110: bufpush(0x0111); break; case 0x0112: bufpush(0x0113); break; case 0x0114: bufpush(0x0115); break; case 0x0116: bufpush(0x0117); break; case 0x0118: bufpush(0x0119); break; case 0x011A: bufpush(0x011B); break; case 0x011C: bufpush(0x011D); break; case 0x011E: bufpush(0x011F); break; case 0x0120: bufpush(0x0121); break; case 0x0122: bufpush(0x0123); break; case 0x0124: bufpush(0x0125); break; case 0x0126: bufpush(0x0127); break; case 0x0128: bufpush(0x0129); break; case 0x012A: bufpush(0x012B); break; case 0x012C: bufpush(0x012D); break; case 0x012E: bufpush(0x012F); break; case 0x0130: bufpush(0x0069); bufpush(0x0307); break; case 0x0132: bufpush(0x0133); break; case 0x0134: bufpush(0x0135); break; case 0x0136: bufpush(0x0137); break; case 0x0139: bufpush(0x013A); break; case 0x013B: bufpush(0x013C); break; case 0x013D: bufpush(0x013E); break; case 0x013F: bufpush(0x0140); break; case 0x0141: bufpush(0x0142); break; case 0x0143: bufpush(0x0144); break; case 0x0145: bufpush(0x0146); break; case 0x0147: bufpush(0x0148); break; case 0x0149: bufpush(0x02BC); bufpush(0x006E); break; case 0x014A: bufpush(0x014B); break; case 0x014C: bufpush(0x014D); break; case 0x014E: bufpush(0x014F); break; case 0x0150: bufpush(0x0151); break; case 0x0152: bufpush(0x0153); break; case 0x0154: bufpush(0x0155); break; case 0x0156: bufpush(0x0157); break; case 0x0158: bufpush(0x0159); break; case 0x015A: bufpush(0x015B); break; case 0x015C: bufpush(0x015D); break; case 0x015E: bufpush(0x015F); break; case 0x0160: bufpush(0x0161); break; case 0x0162: bufpush(0x0163); break; case 0x0164: bufpush(0x0165); break; case 0x0166: bufpush(0x0167); break; case 0x0168: bufpush(0x0169); break; case 0x016A: bufpush(0x016B); break; case 0x016C: bufpush(0x016D); break; case 0x016E: bufpush(0x016F); break; case 0x0170: bufpush(0x0171); break; case 0x0172: bufpush(0x0173); break; case 0x0174: bufpush(0x0175); break; case 0x0176: bufpush(0x0177); break; case 0x0178: bufpush(0x00FF); break; case 0x0179: bufpush(0x017A); break; case 0x017B: bufpush(0x017C); break; case 0x017D: bufpush(0x017E); break; case 0x017F: bufpush(0x0073); break; case 0x0181: bufpush(0x0253); break; case 0x0182: bufpush(0x0183); break; case 0x0184: bufpush(0x0185); break; case 0x0186: bufpush(0x0254); break; case 0x0187: bufpush(0x0188); break; case 0x0189: bufpush(0x0256); break; case 0x018A: bufpush(0x0257); break; case 0x018B: bufpush(0x018C); break; case 0x018E: bufpush(0x01DD); break; case 0x018F: bufpush(0x0259); break; case 0x0190: bufpush(0x025B); break; case 0x0191: bufpush(0x0192); break; case 0x0193: bufpush(0x0260); break; case 0x0194: bufpush(0x0263); break; case 0x0196: bufpush(0x0269); break; case 0x0197: bufpush(0x0268); break; case 0x0198: bufpush(0x0199); break; case 0x019C: bufpush(0x026F); break; case 0x019D: bufpush(0x0272); break; case 0x019F: bufpush(0x0275); break; case 0x01A0: bufpush(0x01A1); break; case 0x01A2: bufpush(0x01A3); break; case 0x01A4: bufpush(0x01A5); break; case 0x01A6: bufpush(0x0280); break; case 0x01A7: bufpush(0x01A8); break; case 0x01A9: bufpush(0x0283); break; case 0x01AC: bufpush(0x01AD); break; case 0x01AE: bufpush(0x0288); break; case 0x01AF: bufpush(0x01B0); break; case 0x01B1: bufpush(0x028A); break; case 0x01B2: bufpush(0x028B); break; case 0x01B3: bufpush(0x01B4); break; case 0x01B5: bufpush(0x01B6); break; case 0x01B7: bufpush(0x0292); break; case 0x01B8: bufpush(0x01B9); break; case 0x01BC: bufpush(0x01BD); break; case 0x01C4: bufpush(0x01C6); break; case 0x01C5: bufpush(0x01C6); break; case 0x01C7: bufpush(0x01C9); break; case 0x01C8: bufpush(0x01C9); break; case 0x01CA: bufpush(0x01CC); break; case 0x01CB: bufpush(0x01CC); break; case 0x01CD: bufpush(0x01CE); break; case 0x01CF: bufpush(0x01D0); break; case 0x01D1: bufpush(0x01D2); break; case 0x01D3: bufpush(0x01D4); break; case 0x01D5: bufpush(0x01D6); break; case 0x01D7: bufpush(0x01D8); break; case 0x01D9: bufpush(0x01DA); break; case 0x01DB: bufpush(0x01DC); break; case 0x01DE: bufpush(0x01DF); break; case 0x01E0: bufpush(0x01E1); break; case 0x01E2: bufpush(0x01E3); break; case 0x01E4: bufpush(0x01E5); break; case 0x01E6: bufpush(0x01E7); break; case 0x01E8: bufpush(0x01E9); break; case 0x01EA: bufpush(0x01EB); break; case 0x01EC: bufpush(0x01ED); break; case 0x01EE: bufpush(0x01EF); break; case 0x01F0: bufpush(0x006A); bufpush(0x030C); break; case 0x01F1: bufpush(0x01F3); break; case 0x01F2: bufpush(0x01F3); break; case 0x01F4: bufpush(0x01F5); break; case 0x01F6: bufpush(0x0195); break; case 0x01F7: bufpush(0x01BF); break; case 0x01F8: bufpush(0x01F9); break; case 0x01FA: bufpush(0x01FB); break; case 0x01FC: bufpush(0x01FD); break; case 0x01FE: bufpush(0x01FF); break; case 0x0200: bufpush(0x0201); break; case 0x0202: bufpush(0x0203); break; case 0x0204: bufpush(0x0205); break; case 0x0206: bufpush(0x0207); break; case 0x0208: bufpush(0x0209); break; case 0x020A: bufpush(0x020B); break; case 0x020C: bufpush(0x020D); break; case 0x020E: bufpush(0x020F); break; case 0x0210: bufpush(0x0211); break; case 0x0212: bufpush(0x0213); break; case 0x0214: bufpush(0x0215); break; case 0x0216: bufpush(0x0217); break; case 0x0218: bufpush(0x0219); break; case 0x021A: bufpush(0x021B); break; case 0x021C: bufpush(0x021D); break; case 0x021E: bufpush(0x021F); break; case 0x0220: bufpush(0x019E); break; case 0x0222: bufpush(0x0223); break; case 0x0224: bufpush(0x0225); break; case 0x0226: bufpush(0x0227); break; case 0x0228: bufpush(0x0229); break; case 0x022A: bufpush(0x022B); break; case 0x022C: bufpush(0x022D); break; case 0x022E: bufpush(0x022F); break; case 0x0230: bufpush(0x0231); break; case 0x0232: bufpush(0x0233); break; case 0x023A: bufpush(0x2C65); break; case 0x023B: bufpush(0x023C); break; case 0x023D: bufpush(0x019A); break; case 0x023E: bufpush(0x2C66); break; case 0x0241: bufpush(0x0242); break; case 0x0243: bufpush(0x0180); break; case 0x0244: bufpush(0x0289); break; case 0x0245: bufpush(0x028C); break; case 0x0246: bufpush(0x0247); break; case 0x0248: bufpush(0x0249); break; case 0x024A: bufpush(0x024B); break; case 0x024C: bufpush(0x024D); break; case 0x024E: bufpush(0x024F); break; case 0x0345: bufpush(0x03B9); break; case 0x0370: bufpush(0x0371); break; case 0x0372: bufpush(0x0373); break; case 0x0376: bufpush(0x0377); break; case 0x037F: bufpush(0x03F3); break; case 0x0386: bufpush(0x03AC); break; case 0x0388: bufpush(0x03AD); break; case 0x0389: bufpush(0x03AE); break; case 0x038A: bufpush(0x03AF); break; case 0x038C: bufpush(0x03CC); break; case 0x038E: bufpush(0x03CD); break; case 0x038F: bufpush(0x03CE); break; case 0x0390: bufpush(0x03B9); bufpush(0x0308); bufpush(0x0301); break; case 0x0391: bufpush(0x03B1); break; case 0x0392: bufpush(0x03B2); break; case 0x0393: bufpush(0x03B3); break; case 0x0394: bufpush(0x03B4); break; case 0x0395: bufpush(0x03B5); break; case 0x0396: bufpush(0x03B6); break; case 0x0397: bufpush(0x03B7); break; case 0x0398: bufpush(0x03B8); break; case 0x0399: bufpush(0x03B9); break; case 0x039A: bufpush(0x03BA); break; case 0x039B: bufpush(0x03BB); break; case 0x039C: bufpush(0x03BC); break; case 0x039D: bufpush(0x03BD); break; case 0x039E: bufpush(0x03BE); break; case 0x039F: bufpush(0x03BF); break; case 0x03A0: bufpush(0x03C0); break; case 0x03A1: bufpush(0x03C1); break; case 0x03A3: bufpush(0x03C3); break; case 0x03A4: bufpush(0x03C4); break; case 0x03A5: bufpush(0x03C5); break; case 0x03A6: bufpush(0x03C6); break; case 0x03A7: bufpush(0x03C7); break; case 0x03A8: bufpush(0x03C8); break; case 0x03A9: bufpush(0x03C9); break; case 0x03AA: bufpush(0x03CA); break; case 0x03AB: bufpush(0x03CB); break; case 0x03B0: bufpush(0x03C5); bufpush(0x0308); bufpush(0x0301); break; case 0x03C2: bufpush(0x03C3); break; case 0x03CF: bufpush(0x03D7); break; case 0x03D0: bufpush(0x03B2); break; case 0x03D1: bufpush(0x03B8); break; case 0x03D5: bufpush(0x03C6); break; case 0x03D6: bufpush(0x03C0); break; case 0x03D8: bufpush(0x03D9); break; case 0x03DA: bufpush(0x03DB); break; case 0x03DC: bufpush(0x03DD); break; case 0x03DE: bufpush(0x03DF); break; case 0x03E0: bufpush(0x03E1); break; case 0x03E2: bufpush(0x03E3); break; case 0x03E4: bufpush(0x03E5); break; case 0x03E6: bufpush(0x03E7); break; case 0x03E8: bufpush(0x03E9); break; case 0x03EA: bufpush(0x03EB); break; case 0x03EC: bufpush(0x03ED); break; case 0x03EE: bufpush(0x03EF); break; case 0x03F0: bufpush(0x03BA); break; case 0x03F1: bufpush(0x03C1); break; case 0x03F4: bufpush(0x03B8); break; case 0x03F5: bufpush(0x03B5); break; case 0x03F7: bufpush(0x03F8); break; case 0x03F9: bufpush(0x03F2); break; case 0x03FA: bufpush(0x03FB); break; case 0x03FD: bufpush(0x037B); break; case 0x03FE: bufpush(0x037C); break; case 0x03FF: bufpush(0x037D); break; case 0x0400: bufpush(0x0450); break; case 0x0401: bufpush(0x0451); break; case 0x0402: bufpush(0x0452); break; case 0x0403: bufpush(0x0453); break; case 0x0404: bufpush(0x0454); break; case 0x0405: bufpush(0x0455); break; case 0x0406: bufpush(0x0456); break; case 0x0407: bufpush(0x0457); break; case 0x0408: bufpush(0x0458); break; case 0x0409: bufpush(0x0459); break; case 0x040A: bufpush(0x045A); break; case 0x040B: bufpush(0x045B); break; case 0x040C: bufpush(0x045C); break; case 0x040D: bufpush(0x045D); break; case 0x040E: bufpush(0x045E); break; case 0x040F: bufpush(0x045F); break; case 0x0410: bufpush(0x0430); break; case 0x0411: bufpush(0x0431); break; case 0x0412: bufpush(0x0432); break; case 0x0413: bufpush(0x0433); break; case 0x0414: bufpush(0x0434); break; case 0x0415: bufpush(0x0435); break; case 0x0416: bufpush(0x0436); break; case 0x0417: bufpush(0x0437); break; case 0x0418: bufpush(0x0438); break; case 0x0419: bufpush(0x0439); break; case 0x041A: bufpush(0x043A); break; case 0x041B: bufpush(0x043B); break; case 0x041C: bufpush(0x043C); break; case 0x041D: bufpush(0x043D); break; case 0x041E: bufpush(0x043E); break; case 0x041F: bufpush(0x043F); break; case 0x0420: bufpush(0x0440); break; case 0x0421: bufpush(0x0441); break; case 0x0422: bufpush(0x0442); break; case 0x0423: bufpush(0x0443); break; case 0x0424: bufpush(0x0444); break; case 0x0425: bufpush(0x0445); break; case 0x0426: bufpush(0x0446); break; case 0x0427: bufpush(0x0447); break; case 0x0428: bufpush(0x0448); break; case 0x0429: bufpush(0x0449); break; case 0x042A: bufpush(0x044A); break; case 0x042B: bufpush(0x044B); break; case 0x042C: bufpush(0x044C); break; case 0x042D: bufpush(0x044D); break; case 0x042E: bufpush(0x044E); break; case 0x042F: bufpush(0x044F); break; case 0x0460: bufpush(0x0461); break; case 0x0462: bufpush(0x0463); break; case 0x0464: bufpush(0x0465); break; case 0x0466: bufpush(0x0467); break; case 0x0468: bufpush(0x0469); break; case 0x046A: bufpush(0x046B); break; case 0x046C: bufpush(0x046D); break; case 0x046E: bufpush(0x046F); break; case 0x0470: bufpush(0x0471); break; case 0x0472: bufpush(0x0473); break; case 0x0474: bufpush(0x0475); break; case 0x0476: bufpush(0x0477); break; case 0x0478: bufpush(0x0479); break; case 0x047A: bufpush(0x047B); break; case 0x047C: bufpush(0x047D); break; case 0x047E: bufpush(0x047F); break; case 0x0480: bufpush(0x0481); break; case 0x048A: bufpush(0x048B); break; case 0x048C: bufpush(0x048D); break; case 0x048E: bufpush(0x048F); break; case 0x0490: bufpush(0x0491); break; case 0x0492: bufpush(0x0493); break; case 0x0494: bufpush(0x0495); break; case 0x0496: bufpush(0x0497); break; case 0x0498: bufpush(0x0499); break; case 0x049A: bufpush(0x049B); break; case 0x049C: bufpush(0x049D); break; case 0x049E: bufpush(0x049F); break; case 0x04A0: bufpush(0x04A1); break; case 0x04A2: bufpush(0x04A3); break; case 0x04A4: bufpush(0x04A5); break; case 0x04A6: bufpush(0x04A7); break; case 0x04A8: bufpush(0x04A9); break; case 0x04AA: bufpush(0x04AB); break; case 0x04AC: bufpush(0x04AD); break; case 0x04AE: bufpush(0x04AF); break; case 0x04B0: bufpush(0x04B1); break; case 0x04B2: bufpush(0x04B3); break; case 0x04B4: bufpush(0x04B5); break; case 0x04B6: bufpush(0x04B7); break; case 0x04B8: bufpush(0x04B9); break; case 0x04BA: bufpush(0x04BB); break; case 0x04BC: bufpush(0x04BD); break; case 0x04BE: bufpush(0x04BF); break; case 0x04C0: bufpush(0x04CF); break; case 0x04C1: bufpush(0x04C2); break; case 0x04C3: bufpush(0x04C4); break; case 0x04C5: bufpush(0x04C6); break; case 0x04C7: bufpush(0x04C8); break; case 0x04C9: bufpush(0x04CA); break; case 0x04CB: bufpush(0x04CC); break; case 0x04CD: bufpush(0x04CE); break; case 0x04D0: bufpush(0x04D1); break; case 0x04D2: bufpush(0x04D3); break; case 0x04D4: bufpush(0x04D5); break; case 0x04D6: bufpush(0x04D7); break; case 0x04D8: bufpush(0x04D9); break; case 0x04DA: bufpush(0x04DB); break; case 0x04DC: bufpush(0x04DD); break; case 0x04DE: bufpush(0x04DF); break; case 0x04E0: bufpush(0x04E1); break; case 0x04E2: bufpush(0x04E3); break; case 0x04E4: bufpush(0x04E5); break; case 0x04E6: bufpush(0x04E7); break; case 0x04E8: bufpush(0x04E9); break; case 0x04EA: bufpush(0x04EB); break; case 0x04EC: bufpush(0x04ED); break; case 0x04EE: bufpush(0x04EF); break; case 0x04F0: bufpush(0x04F1); break; case 0x04F2: bufpush(0x04F3); break; case 0x04F4: bufpush(0x04F5); break; case 0x04F6: bufpush(0x04F7); break; case 0x04F8: bufpush(0x04F9); break; case 0x04FA: bufpush(0x04FB); break; case 0x04FC: bufpush(0x04FD); break; case 0x04FE: bufpush(0x04FF); break; case 0x0500: bufpush(0x0501); break; case 0x0502: bufpush(0x0503); break; case 0x0504: bufpush(0x0505); break; case 0x0506: bufpush(0x0507); break; case 0x0508: bufpush(0x0509); break; case 0x050A: bufpush(0x050B); break; case 0x050C: bufpush(0x050D); break; case 0x050E: bufpush(0x050F); break; case 0x0510: bufpush(0x0511); break; case 0x0512: bufpush(0x0513); break; case 0x0514: bufpush(0x0515); break; case 0x0516: bufpush(0x0517); break; case 0x0518: bufpush(0x0519); break; case 0x051A: bufpush(0x051B); break; case 0x051C: bufpush(0x051D); break; case 0x051E: bufpush(0x051F); break; case 0x0520: bufpush(0x0521); break; case 0x0522: bufpush(0x0523); break; case 0x0524: bufpush(0x0525); break; case 0x0526: bufpush(0x0527); break; case 0x0528: bufpush(0x0529); break; case 0x052A: bufpush(0x052B); break; case 0x052C: bufpush(0x052D); break; case 0x052E: bufpush(0x052F); break; case 0x0531: bufpush(0x0561); break; case 0x0532: bufpush(0x0562); break; case 0x0533: bufpush(0x0563); break; case 0x0534: bufpush(0x0564); break; case 0x0535: bufpush(0x0565); break; case 0x0536: bufpush(0x0566); break; case 0x0537: bufpush(0x0567); break; case 0x0538: bufpush(0x0568); break; case 0x0539: bufpush(0x0569); break; case 0x053A: bufpush(0x056A); break; case 0x053B: bufpush(0x056B); break; case 0x053C: bufpush(0x056C); break; case 0x053D: bufpush(0x056D); break; case 0x053E: bufpush(0x056E); break; case 0x053F: bufpush(0x056F); break; case 0x0540: bufpush(0x0570); break; case 0x0541: bufpush(0x0571); break; case 0x0542: bufpush(0x0572); break; case 0x0543: bufpush(0x0573); break; case 0x0544: bufpush(0x0574); break; case 0x0545: bufpush(0x0575); break; case 0x0546: bufpush(0x0576); break; case 0x0547: bufpush(0x0577); break; case 0x0548: bufpush(0x0578); break; case 0x0549: bufpush(0x0579); break; case 0x054A: bufpush(0x057A); break; case 0x054B: bufpush(0x057B); break; case 0x054C: bufpush(0x057C); break; case 0x054D: bufpush(0x057D); break; case 0x054E: bufpush(0x057E); break; case 0x054F: bufpush(0x057F); break; case 0x0550: bufpush(0x0580); break; case 0x0551: bufpush(0x0581); break; case 0x0552: bufpush(0x0582); break; case 0x0553: bufpush(0x0583); break; case 0x0554: bufpush(0x0584); break; case 0x0555: bufpush(0x0585); break; case 0x0556: bufpush(0x0586); break; case 0x0587: bufpush(0x0565); bufpush(0x0582); break; case 0x10A0: bufpush(0x2D00); break; case 0x10A1: bufpush(0x2D01); break; case 0x10A2: bufpush(0x2D02); break; case 0x10A3: bufpush(0x2D03); break; case 0x10A4: bufpush(0x2D04); break; case 0x10A5: bufpush(0x2D05); break; case 0x10A6: bufpush(0x2D06); break; case 0x10A7: bufpush(0x2D07); break; case 0x10A8: bufpush(0x2D08); break; case 0x10A9: bufpush(0x2D09); break; case 0x10AA: bufpush(0x2D0A); break; case 0x10AB: bufpush(0x2D0B); break; case 0x10AC: bufpush(0x2D0C); break; case 0x10AD: bufpush(0x2D0D); break; case 0x10AE: bufpush(0x2D0E); break; case 0x10AF: bufpush(0x2D0F); break; case 0x10B0: bufpush(0x2D10); break; case 0x10B1: bufpush(0x2D11); break; case 0x10B2: bufpush(0x2D12); break; case 0x10B3: bufpush(0x2D13); break; case 0x10B4: bufpush(0x2D14); break; case 0x10B5: bufpush(0x2D15); break; case 0x10B6: bufpush(0x2D16); break; case 0x10B7: bufpush(0x2D17); break; case 0x10B8: bufpush(0x2D18); break; case 0x10B9: bufpush(0x2D19); break; case 0x10BA: bufpush(0x2D1A); break; case 0x10BB: bufpush(0x2D1B); break; case 0x10BC: bufpush(0x2D1C); break; case 0x10BD: bufpush(0x2D1D); break; case 0x10BE: bufpush(0x2D1E); break; case 0x10BF: bufpush(0x2D1F); break; case 0x10C0: bufpush(0x2D20); break; case 0x10C1: bufpush(0x2D21); break; case 0x10C2: bufpush(0x2D22); break; case 0x10C3: bufpush(0x2D23); break; case 0x10C4: bufpush(0x2D24); break; case 0x10C5: bufpush(0x2D25); break; case 0x10C7: bufpush(0x2D27); break; case 0x10CD: bufpush(0x2D2D); break; case 0x13F8: bufpush(0x13F0); break; case 0x13F9: bufpush(0x13F1); break; case 0x13FA: bufpush(0x13F2); break; case 0x13FB: bufpush(0x13F3); break; case 0x13FC: bufpush(0x13F4); break; case 0x13FD: bufpush(0x13F5); break; case 0x1C80: bufpush(0x0432); break; case 0x1C81: bufpush(0x0434); break; case 0x1C82: bufpush(0x043E); break; case 0x1C83: bufpush(0x0441); break; case 0x1C84: bufpush(0x0442); break; case 0x1C85: bufpush(0x0442); break; case 0x1C86: bufpush(0x044A); break; case 0x1C87: bufpush(0x0463); break; case 0x1C88: bufpush(0xA64B); break; case 0x1E00: bufpush(0x1E01); break; case 0x1E02: bufpush(0x1E03); break; case 0x1E04: bufpush(0x1E05); break; case 0x1E06: bufpush(0x1E07); break; case 0x1E08: bufpush(0x1E09); break; case 0x1E0A: bufpush(0x1E0B); break; case 0x1E0C: bufpush(0x1E0D); break; case 0x1E0E: bufpush(0x1E0F); break; case 0x1E10: bufpush(0x1E11); break; case 0x1E12: bufpush(0x1E13); break; case 0x1E14: bufpush(0x1E15); break; case 0x1E16: bufpush(0x1E17); break; case 0x1E18: bufpush(0x1E19); break; case 0x1E1A: bufpush(0x1E1B); break; case 0x1E1C: bufpush(0x1E1D); break; case 0x1E1E: bufpush(0x1E1F); break; case 0x1E20: bufpush(0x1E21); break; case 0x1E22: bufpush(0x1E23); break; case 0x1E24: bufpush(0x1E25); break; case 0x1E26: bufpush(0x1E27); break; case 0x1E28: bufpush(0x1E29); break; case 0x1E2A: bufpush(0x1E2B); break; case 0x1E2C: bufpush(0x1E2D); break; case 0x1E2E: bufpush(0x1E2F); break; case 0x1E30: bufpush(0x1E31); break; case 0x1E32: bufpush(0x1E33); break; case 0x1E34: bufpush(0x1E35); break; case 0x1E36: bufpush(0x1E37); break; case 0x1E38: bufpush(0x1E39); break; case 0x1E3A: bufpush(0x1E3B); break; case 0x1E3C: bufpush(0x1E3D); break; case 0x1E3E: bufpush(0x1E3F); break; case 0x1E40: bufpush(0x1E41); break; case 0x1E42: bufpush(0x1E43); break; case 0x1E44: bufpush(0x1E45); break; case 0x1E46: bufpush(0x1E47); break; case 0x1E48: bufpush(0x1E49); break; case 0x1E4A: bufpush(0x1E4B); break; case 0x1E4C: bufpush(0x1E4D); break; case 0x1E4E: bufpush(0x1E4F); break; case 0x1E50: bufpush(0x1E51); break; case 0x1E52: bufpush(0x1E53); break; case 0x1E54: bufpush(0x1E55); break; case 0x1E56: bufpush(0x1E57); break; case 0x1E58: bufpush(0x1E59); break; case 0x1E5A: bufpush(0x1E5B); break; case 0x1E5C: bufpush(0x1E5D); break; case 0x1E5E: bufpush(0x1E5F); break; case 0x1E60: bufpush(0x1E61); break; case 0x1E62: bufpush(0x1E63); break; case 0x1E64: bufpush(0x1E65); break; case 0x1E66: bufpush(0x1E67); break; case 0x1E68: bufpush(0x1E69); break; case 0x1E6A: bufpush(0x1E6B); break; case 0x1E6C: bufpush(0x1E6D); break; case 0x1E6E: bufpush(0x1E6F); break; case 0x1E70: bufpush(0x1E71); break; case 0x1E72: bufpush(0x1E73); break; case 0x1E74: bufpush(0x1E75); break; case 0x1E76: bufpush(0x1E77); break; case 0x1E78: bufpush(0x1E79); break; case 0x1E7A: bufpush(0x1E7B); break; case 0x1E7C: bufpush(0x1E7D); break; case 0x1E7E: bufpush(0x1E7F); break; case 0x1E80: bufpush(0x1E81); break; case 0x1E82: bufpush(0x1E83); break; case 0x1E84: bufpush(0x1E85); break; case 0x1E86: bufpush(0x1E87); break; case 0x1E88: bufpush(0x1E89); break; case 0x1E8A: bufpush(0x1E8B); break; case 0x1E8C: bufpush(0x1E8D); break; case 0x1E8E: bufpush(0x1E8F); break; case 0x1E90: bufpush(0x1E91); break; case 0x1E92: bufpush(0x1E93); break; case 0x1E94: bufpush(0x1E95); break; case 0x1E96: bufpush(0x0068); bufpush(0x0331); break; case 0x1E97: bufpush(0x0074); bufpush(0x0308); break; case 0x1E98: bufpush(0x0077); bufpush(0x030A); break; case 0x1E99: bufpush(0x0079); bufpush(0x030A); break; case 0x1E9A: bufpush(0x0061); bufpush(0x02BE); break; case 0x1E9B: bufpush(0x1E61); break; case 0x1E9E: bufpush(0x0073); bufpush(0x0073); break; case 0x1EA0: bufpush(0x1EA1); break; case 0x1EA2: bufpush(0x1EA3); break; case 0x1EA4: bufpush(0x1EA5); break; case 0x1EA6: bufpush(0x1EA7); break; case 0x1EA8: bufpush(0x1EA9); break; case 0x1EAA: bufpush(0x1EAB); break; case 0x1EAC: bufpush(0x1EAD); break; case 0x1EAE: bufpush(0x1EAF); break; case 0x1EB0: bufpush(0x1EB1); break; case 0x1EB2: bufpush(0x1EB3); break; case 0x1EB4: bufpush(0x1EB5); break; case 0x1EB6: bufpush(0x1EB7); break; case 0x1EB8: bufpush(0x1EB9); break; case 0x1EBA: bufpush(0x1EBB); break; case 0x1EBC: bufpush(0x1EBD); break; case 0x1EBE: bufpush(0x1EBF); break; case 0x1EC0: bufpush(0x1EC1); break; case 0x1EC2: bufpush(0x1EC3); break; case 0x1EC4: bufpush(0x1EC5); break; case 0x1EC6: bufpush(0x1EC7); break; case 0x1EC8: bufpush(0x1EC9); break; case 0x1ECA: bufpush(0x1ECB); break; case 0x1ECC: bufpush(0x1ECD); break; case 0x1ECE: bufpush(0x1ECF); break; case 0x1ED0: bufpush(0x1ED1); break; case 0x1ED2: bufpush(0x1ED3); break; case 0x1ED4: bufpush(0x1ED5); break; case 0x1ED6: bufpush(0x1ED7); break; case 0x1ED8: bufpush(0x1ED9); break; case 0x1EDA: bufpush(0x1EDB); break; case 0x1EDC: bufpush(0x1EDD); break; case 0x1EDE: bufpush(0x1EDF); break; case 0x1EE0: bufpush(0x1EE1); break; case 0x1EE2: bufpush(0x1EE3); break; case 0x1EE4: bufpush(0x1EE5); break; case 0x1EE6: bufpush(0x1EE7); break; case 0x1EE8: bufpush(0x1EE9); break; case 0x1EEA: bufpush(0x1EEB); break; case 0x1EEC: bufpush(0x1EED); break; case 0x1EEE: bufpush(0x1EEF); break; case 0x1EF0: bufpush(0x1EF1); break; case 0x1EF2: bufpush(0x1EF3); break; case 0x1EF4: bufpush(0x1EF5); break; case 0x1EF6: bufpush(0x1EF7); break; case 0x1EF8: bufpush(0x1EF9); break; case 0x1EFA: bufpush(0x1EFB); break; case 0x1EFC: bufpush(0x1EFD); break; case 0x1EFE: bufpush(0x1EFF); break; case 0x1F08: bufpush(0x1F00); break; case 0x1F09: bufpush(0x1F01); break; case 0x1F0A: bufpush(0x1F02); break; case 0x1F0B: bufpush(0x1F03); break; case 0x1F0C: bufpush(0x1F04); break; case 0x1F0D: bufpush(0x1F05); break; case 0x1F0E: bufpush(0x1F06); break; case 0x1F0F: bufpush(0x1F07); break; case 0x1F18: bufpush(0x1F10); break; case 0x1F19: bufpush(0x1F11); break; case 0x1F1A: bufpush(0x1F12); break; case 0x1F1B: bufpush(0x1F13); break; case 0x1F1C: bufpush(0x1F14); break; case 0x1F1D: bufpush(0x1F15); break; case 0x1F28: bufpush(0x1F20); break; case 0x1F29: bufpush(0x1F21); break; case 0x1F2A: bufpush(0x1F22); break; case 0x1F2B: bufpush(0x1F23); break; case 0x1F2C: bufpush(0x1F24); break; case 0x1F2D: bufpush(0x1F25); break; case 0x1F2E: bufpush(0x1F26); break; case 0x1F2F: bufpush(0x1F27); break; case 0x1F38: bufpush(0x1F30); break; case 0x1F39: bufpush(0x1F31); break; case 0x1F3A: bufpush(0x1F32); break; case 0x1F3B: bufpush(0x1F33); break; case 0x1F3C: bufpush(0x1F34); break; case 0x1F3D: bufpush(0x1F35); break; case 0x1F3E: bufpush(0x1F36); break; case 0x1F3F: bufpush(0x1F37); break; case 0x1F48: bufpush(0x1F40); break; case 0x1F49: bufpush(0x1F41); break; case 0x1F4A: bufpush(0x1F42); break; case 0x1F4B: bufpush(0x1F43); break; case 0x1F4C: bufpush(0x1F44); break; case 0x1F4D: bufpush(0x1F45); break; case 0x1F50: bufpush(0x03C5); bufpush(0x0313); break; case 0x1F52: bufpush(0x03C5); bufpush(0x0313); bufpush(0x0300); break; case 0x1F54: bufpush(0x03C5); bufpush(0x0313); bufpush(0x0301); break; case 0x1F56: bufpush(0x03C5); bufpush(0x0313); bufpush(0x0342); break; case 0x1F59: bufpush(0x1F51); break; case 0x1F5B: bufpush(0x1F53); break; case 0x1F5D: bufpush(0x1F55); break; case 0x1F5F: bufpush(0x1F57); break; case 0x1F68: bufpush(0x1F60); break; case 0x1F69: bufpush(0x1F61); break; case 0x1F6A: bufpush(0x1F62); break; case 0x1F6B: bufpush(0x1F63); break; case 0x1F6C: bufpush(0x1F64); break; case 0x1F6D: bufpush(0x1F65); break; case 0x1F6E: bufpush(0x1F66); break; case 0x1F6F: bufpush(0x1F67); break; case 0x1F80: bufpush(0x1F00); bufpush(0x03B9); break; case 0x1F81: bufpush(0x1F01); bufpush(0x03B9); break; case 0x1F82: bufpush(0x1F02); bufpush(0x03B9); break; case 0x1F83: bufpush(0x1F03); bufpush(0x03B9); break; case 0x1F84: bufpush(0x1F04); bufpush(0x03B9); break; case 0x1F85: bufpush(0x1F05); bufpush(0x03B9); break; case 0x1F86: bufpush(0x1F06); bufpush(0x03B9); break; case 0x1F87: bufpush(0x1F07); bufpush(0x03B9); break; case 0x1F88: bufpush(0x1F00); bufpush(0x03B9); break; case 0x1F89: bufpush(0x1F01); bufpush(0x03B9); break; case 0x1F8A: bufpush(0x1F02); bufpush(0x03B9); break; case 0x1F8B: bufpush(0x1F03); bufpush(0x03B9); break; case 0x1F8C: bufpush(0x1F04); bufpush(0x03B9); break; case 0x1F8D: bufpush(0x1F05); bufpush(0x03B9); break; case 0x1F8E: bufpush(0x1F06); bufpush(0x03B9); break; case 0x1F8F: bufpush(0x1F07); bufpush(0x03B9); break; case 0x1F90: bufpush(0x1F20); bufpush(0x03B9); break; case 0x1F91: bufpush(0x1F21); bufpush(0x03B9); break; case 0x1F92: bufpush(0x1F22); bufpush(0x03B9); break; case 0x1F93: bufpush(0x1F23); bufpush(0x03B9); break; case 0x1F94: bufpush(0x1F24); bufpush(0x03B9); break; case 0x1F95: bufpush(0x1F25); bufpush(0x03B9); break; case 0x1F96: bufpush(0x1F26); bufpush(0x03B9); break; case 0x1F97: bufpush(0x1F27); bufpush(0x03B9); break; case 0x1F98: bufpush(0x1F20); bufpush(0x03B9); break; case 0x1F99: bufpush(0x1F21); bufpush(0x03B9); break; case 0x1F9A: bufpush(0x1F22); bufpush(0x03B9); break; case 0x1F9B: bufpush(0x1F23); bufpush(0x03B9); break; case 0x1F9C: bufpush(0x1F24); bufpush(0x03B9); break; case 0x1F9D: bufpush(0x1F25); bufpush(0x03B9); break; case 0x1F9E: bufpush(0x1F26); bufpush(0x03B9); break; case 0x1F9F: bufpush(0x1F27); bufpush(0x03B9); break; case 0x1FA0: bufpush(0x1F60); bufpush(0x03B9); break; case 0x1FA1: bufpush(0x1F61); bufpush(0x03B9); break; case 0x1FA2: bufpush(0x1F62); bufpush(0x03B9); break; case 0x1FA3: bufpush(0x1F63); bufpush(0x03B9); break; case 0x1FA4: bufpush(0x1F64); bufpush(0x03B9); break; case 0x1FA5: bufpush(0x1F65); bufpush(0x03B9); break; case 0x1FA6: bufpush(0x1F66); bufpush(0x03B9); break; case 0x1FA7: bufpush(0x1F67); bufpush(0x03B9); break; case 0x1FA8: bufpush(0x1F60); bufpush(0x03B9); break; case 0x1FA9: bufpush(0x1F61); bufpush(0x03B9); break; case 0x1FAA: bufpush(0x1F62); bufpush(0x03B9); break; case 0x1FAB: bufpush(0x1F63); bufpush(0x03B9); break; case 0x1FAC: bufpush(0x1F64); bufpush(0x03B9); break; case 0x1FAD: bufpush(0x1F65); bufpush(0x03B9); break; case 0x1FAE: bufpush(0x1F66); bufpush(0x03B9); break; case 0x1FAF: bufpush(0x1F67); bufpush(0x03B9); break; case 0x1FB2: bufpush(0x1F70); bufpush(0x03B9); break; case 0x1FB3: bufpush(0x03B1); bufpush(0x03B9); break; case 0x1FB4: bufpush(0x03AC); bufpush(0x03B9); break; case 0x1FB6: bufpush(0x03B1); bufpush(0x0342); break; case 0x1FB7: bufpush(0x03B1); bufpush(0x0342); bufpush(0x03B9); break; case 0x1FB8: bufpush(0x1FB0); break; case 0x1FB9: bufpush(0x1FB1); break; case 0x1FBA: bufpush(0x1F70); break; case 0x1FBB: bufpush(0x1F71); break; case 0x1FBC: bufpush(0x03B1); bufpush(0x03B9); break; case 0x1FBE: bufpush(0x03B9); break; case 0x1FC2: bufpush(0x1F74); bufpush(0x03B9); break; case 0x1FC3: bufpush(0x03B7); bufpush(0x03B9); break; case 0x1FC4: bufpush(0x03AE); bufpush(0x03B9); break; case 0x1FC6: bufpush(0x03B7); bufpush(0x0342); break; case 0x1FC7: bufpush(0x03B7); bufpush(0x0342); bufpush(0x03B9); break; case 0x1FC8: bufpush(0x1F72); break; case 0x1FC9: bufpush(0x1F73); break; case 0x1FCA: bufpush(0x1F74); break; case 0x1FCB: bufpush(0x1F75); break; case 0x1FCC: bufpush(0x03B7); bufpush(0x03B9); break; case 0x1FD2: bufpush(0x03B9); bufpush(0x0308); bufpush(0x0300); break; case 0x1FD3: bufpush(0x03B9); bufpush(0x0308); bufpush(0x0301); break; case 0x1FD6: bufpush(0x03B9); bufpush(0x0342); break; case 0x1FD7: bufpush(0x03B9); bufpush(0x0308); bufpush(0x0342); break; case 0x1FD8: bufpush(0x1FD0); break; case 0x1FD9: bufpush(0x1FD1); break; case 0x1FDA: bufpush(0x1F76); break; case 0x1FDB: bufpush(0x1F77); break; case 0x1FE2: bufpush(0x03C5); bufpush(0x0308); bufpush(0x0300); break; case 0x1FE3: bufpush(0x03C5); bufpush(0x0308); bufpush(0x0301); break; case 0x1FE4: bufpush(0x03C1); bufpush(0x0313); break; case 0x1FE6: bufpush(0x03C5); bufpush(0x0342); break; case 0x1FE7: bufpush(0x03C5); bufpush(0x0308); bufpush(0x0342); break; case 0x1FE8: bufpush(0x1FE0); break; case 0x1FE9: bufpush(0x1FE1); break; case 0x1FEA: bufpush(0x1F7A); break; case 0x1FEB: bufpush(0x1F7B); break; case 0x1FEC: bufpush(0x1FE5); break; case 0x1FF2: bufpush(0x1F7C); bufpush(0x03B9); break; case 0x1FF3: bufpush(0x03C9); bufpush(0x03B9); break; case 0x1FF4: bufpush(0x03CE); bufpush(0x03B9); break; case 0x1FF6: bufpush(0x03C9); bufpush(0x0342); break; case 0x1FF7: bufpush(0x03C9); bufpush(0x0342); bufpush(0x03B9); break; case 0x1FF8: bufpush(0x1F78); break; case 0x1FF9: bufpush(0x1F79); break; case 0x1FFA: bufpush(0x1F7C); break; case 0x1FFB: bufpush(0x1F7D); break; case 0x1FFC: bufpush(0x03C9); bufpush(0x03B9); break; case 0x2126: bufpush(0x03C9); break; case 0x212A: bufpush(0x006B); break; case 0x212B: bufpush(0x00E5); break; case 0x2132: bufpush(0x214E); break; case 0x2160: bufpush(0x2170); break; case 0x2161: bufpush(0x2171); break; case 0x2162: bufpush(0x2172); break; case 0x2163: bufpush(0x2173); break; case 0x2164: bufpush(0x2174); break; case 0x2165: bufpush(0x2175); break; case 0x2166: bufpush(0x2176); break; case 0x2167: bufpush(0x2177); break; case 0x2168: bufpush(0x2178); break; case 0x2169: bufpush(0x2179); break; case 0x216A: bufpush(0x217A); break; case 0x216B: bufpush(0x217B); break; case 0x216C: bufpush(0x217C); break; case 0x216D: bufpush(0x217D); break; case 0x216E: bufpush(0x217E); break; case 0x216F: bufpush(0x217F); break; case 0x2183: bufpush(0x2184); break; case 0x24B6: bufpush(0x24D0); break; case 0x24B7: bufpush(0x24D1); break; case 0x24B8: bufpush(0x24D2); break; case 0x24B9: bufpush(0x24D3); break; case 0x24BA: bufpush(0x24D4); break; case 0x24BB: bufpush(0x24D5); break; case 0x24BC: bufpush(0x24D6); break; case 0x24BD: bufpush(0x24D7); break; case 0x24BE: bufpush(0x24D8); break; case 0x24BF: bufpush(0x24D9); break; case 0x24C0: bufpush(0x24DA); break; case 0x24C1: bufpush(0x24DB); break; case 0x24C2: bufpush(0x24DC); break; case 0x24C3: bufpush(0x24DD); break; case 0x24C4: bufpush(0x24DE); break; case 0x24C5: bufpush(0x24DF); break; case 0x24C6: bufpush(0x24E0); break; case 0x24C7: bufpush(0x24E1); break; case 0x24C8: bufpush(0x24E2); break; case 0x24C9: bufpush(0x24E3); break; case 0x24CA: bufpush(0x24E4); break; case 0x24CB: bufpush(0x24E5); break; case 0x24CC: bufpush(0x24E6); break; case 0x24CD: bufpush(0x24E7); break; case 0x24CE: bufpush(0x24E8); break; case 0x24CF: bufpush(0x24E9); break; case 0x2C00: bufpush(0x2C30); break; case 0x2C01: bufpush(0x2C31); break; case 0x2C02: bufpush(0x2C32); break; case 0x2C03: bufpush(0x2C33); break; case 0x2C04: bufpush(0x2C34); break; case 0x2C05: bufpush(0x2C35); break; case 0x2C06: bufpush(0x2C36); break; case 0x2C07: bufpush(0x2C37); break; case 0x2C08: bufpush(0x2C38); break; case 0x2C09: bufpush(0x2C39); break; case 0x2C0A: bufpush(0x2C3A); break; case 0x2C0B: bufpush(0x2C3B); break; case 0x2C0C: bufpush(0x2C3C); break; case 0x2C0D: bufpush(0x2C3D); break; case 0x2C0E: bufpush(0x2C3E); break; case 0x2C0F: bufpush(0x2C3F); break; case 0x2C10: bufpush(0x2C40); break; case 0x2C11: bufpush(0x2C41); break; case 0x2C12: bufpush(0x2C42); break; case 0x2C13: bufpush(0x2C43); break; case 0x2C14: bufpush(0x2C44); break; case 0x2C15: bufpush(0x2C45); break; case 0x2C16: bufpush(0x2C46); break; case 0x2C17: bufpush(0x2C47); break; case 0x2C18: bufpush(0x2C48); break; case 0x2C19: bufpush(0x2C49); break; case 0x2C1A: bufpush(0x2C4A); break; case 0x2C1B: bufpush(0x2C4B); break; case 0x2C1C: bufpush(0x2C4C); break; case 0x2C1D: bufpush(0x2C4D); break; case 0x2C1E: bufpush(0x2C4E); break; case 0x2C1F: bufpush(0x2C4F); break; case 0x2C20: bufpush(0x2C50); break; case 0x2C21: bufpush(0x2C51); break; case 0x2C22: bufpush(0x2C52); break; case 0x2C23: bufpush(0x2C53); break; case 0x2C24: bufpush(0x2C54); break; case 0x2C25: bufpush(0x2C55); break; case 0x2C26: bufpush(0x2C56); break; case 0x2C27: bufpush(0x2C57); break; case 0x2C28: bufpush(0x2C58); break; case 0x2C29: bufpush(0x2C59); break; case 0x2C2A: bufpush(0x2C5A); break; case 0x2C2B: bufpush(0x2C5B); break; case 0x2C2C: bufpush(0x2C5C); break; case 0x2C2D: bufpush(0x2C5D); break; case 0x2C2E: bufpush(0x2C5E); break; case 0x2C60: bufpush(0x2C61); break; case 0x2C62: bufpush(0x026B); break; case 0x2C63: bufpush(0x1D7D); break; case 0x2C64: bufpush(0x027D); break; case 0x2C67: bufpush(0x2C68); break; case 0x2C69: bufpush(0x2C6A); break; case 0x2C6B: bufpush(0x2C6C); break; case 0x2C6D: bufpush(0x0251); break; case 0x2C6E: bufpush(0x0271); break; case 0x2C6F: bufpush(0x0250); break; case 0x2C70: bufpush(0x0252); break; case 0x2C72: bufpush(0x2C73); break; case 0x2C75: bufpush(0x2C76); break; case 0x2C7E: bufpush(0x023F); break; case 0x2C7F: bufpush(0x0240); break; case 0x2C80: bufpush(0x2C81); break; case 0x2C82: bufpush(0x2C83); break; case 0x2C84: bufpush(0x2C85); break; case 0x2C86: bufpush(0x2C87); break; case 0x2C88: bufpush(0x2C89); break; case 0x2C8A: bufpush(0x2C8B); break; case 0x2C8C: bufpush(0x2C8D); break; case 0x2C8E: bufpush(0x2C8F); break; case 0x2C90: bufpush(0x2C91); break; case 0x2C92: bufpush(0x2C93); break; case 0x2C94: bufpush(0x2C95); break; case 0x2C96: bufpush(0x2C97); break; case 0x2C98: bufpush(0x2C99); break; case 0x2C9A: bufpush(0x2C9B); break; case 0x2C9C: bufpush(0x2C9D); break; case 0x2C9E: bufpush(0x2C9F); break; case 0x2CA0: bufpush(0x2CA1); break; case 0x2CA2: bufpush(0x2CA3); break; case 0x2CA4: bufpush(0x2CA5); break; case 0x2CA6: bufpush(0x2CA7); break; case 0x2CA8: bufpush(0x2CA9); break; case 0x2CAA: bufpush(0x2CAB); break; case 0x2CAC: bufpush(0x2CAD); break; case 0x2CAE: bufpush(0x2CAF); break; case 0x2CB0: bufpush(0x2CB1); break; case 0x2CB2: bufpush(0x2CB3); break; case 0x2CB4: bufpush(0x2CB5); break; case 0x2CB6: bufpush(0x2CB7); break; case 0x2CB8: bufpush(0x2CB9); break; case 0x2CBA: bufpush(0x2CBB); break; case 0x2CBC: bufpush(0x2CBD); break; case 0x2CBE: bufpush(0x2CBF); break; case 0x2CC0: bufpush(0x2CC1); break; case 0x2CC2: bufpush(0x2CC3); break; case 0x2CC4: bufpush(0x2CC5); break; case 0x2CC6: bufpush(0x2CC7); break; case 0x2CC8: bufpush(0x2CC9); break; case 0x2CCA: bufpush(0x2CCB); break; case 0x2CCC: bufpush(0x2CCD); break; case 0x2CCE: bufpush(0x2CCF); break; case 0x2CD0: bufpush(0x2CD1); break; case 0x2CD2: bufpush(0x2CD3); break; case 0x2CD4: bufpush(0x2CD5); break; case 0x2CD6: bufpush(0x2CD7); break; case 0x2CD8: bufpush(0x2CD9); break; case 0x2CDA: bufpush(0x2CDB); break; case 0x2CDC: bufpush(0x2CDD); break; case 0x2CDE: bufpush(0x2CDF); break; case 0x2CE0: bufpush(0x2CE1); break; case 0x2CE2: bufpush(0x2CE3); break; case 0x2CEB: bufpush(0x2CEC); break; case 0x2CED: bufpush(0x2CEE); break; case 0x2CF2: bufpush(0x2CF3); break; case 0xA640: bufpush(0xA641); break; case 0xA642: bufpush(0xA643); break; case 0xA644: bufpush(0xA645); break; case 0xA646: bufpush(0xA647); break; case 0xA648: bufpush(0xA649); break; case 0xA64A: bufpush(0xA64B); break; case 0xA64C: bufpush(0xA64D); break; case 0xA64E: bufpush(0xA64F); break; case 0xA650: bufpush(0xA651); break; case 0xA652: bufpush(0xA653); break; case 0xA654: bufpush(0xA655); break; case 0xA656: bufpush(0xA657); break; case 0xA658: bufpush(0xA659); break; case 0xA65A: bufpush(0xA65B); break; case 0xA65C: bufpush(0xA65D); break; case 0xA65E: bufpush(0xA65F); break; case 0xA660: bufpush(0xA661); break; case 0xA662: bufpush(0xA663); break; case 0xA664: bufpush(0xA665); break; case 0xA666: bufpush(0xA667); break; case 0xA668: bufpush(0xA669); break; case 0xA66A: bufpush(0xA66B); break; case 0xA66C: bufpush(0xA66D); break; case 0xA680: bufpush(0xA681); break; case 0xA682: bufpush(0xA683); break; case 0xA684: bufpush(0xA685); break; case 0xA686: bufpush(0xA687); break; case 0xA688: bufpush(0xA689); break; case 0xA68A: bufpush(0xA68B); break; case 0xA68C: bufpush(0xA68D); break; case 0xA68E: bufpush(0xA68F); break; case 0xA690: bufpush(0xA691); break; case 0xA692: bufpush(0xA693); break; case 0xA694: bufpush(0xA695); break; case 0xA696: bufpush(0xA697); break; case 0xA698: bufpush(0xA699); break; case 0xA69A: bufpush(0xA69B); break; case 0xA722: bufpush(0xA723); break; case 0xA724: bufpush(0xA725); break; case 0xA726: bufpush(0xA727); break; case 0xA728: bufpush(0xA729); break; case 0xA72A: bufpush(0xA72B); break; case 0xA72C: bufpush(0xA72D); break; case 0xA72E: bufpush(0xA72F); break; case 0xA732: bufpush(0xA733); break; case 0xA734: bufpush(0xA735); break; case 0xA736: bufpush(0xA737); break; case 0xA738: bufpush(0xA739); break; case 0xA73A: bufpush(0xA73B); break; case 0xA73C: bufpush(0xA73D); break; case 0xA73E: bufpush(0xA73F); break; case 0xA740: bufpush(0xA741); break; case 0xA742: bufpush(0xA743); break; case 0xA744: bufpush(0xA745); break; case 0xA746: bufpush(0xA747); break; case 0xA748: bufpush(0xA749); break; case 0xA74A: bufpush(0xA74B); break; case 0xA74C: bufpush(0xA74D); break; case 0xA74E: bufpush(0xA74F); break; case 0xA750: bufpush(0xA751); break; case 0xA752: bufpush(0xA753); break; case 0xA754: bufpush(0xA755); break; case 0xA756: bufpush(0xA757); break; case 0xA758: bufpush(0xA759); break; case 0xA75A: bufpush(0xA75B); break; case 0xA75C: bufpush(0xA75D); break; case 0xA75E: bufpush(0xA75F); break; case 0xA760: bufpush(0xA761); break; case 0xA762: bufpush(0xA763); break; case 0xA764: bufpush(0xA765); break; case 0xA766: bufpush(0xA767); break; case 0xA768: bufpush(0xA769); break; case 0xA76A: bufpush(0xA76B); break; case 0xA76C: bufpush(0xA76D); break; case 0xA76E: bufpush(0xA76F); break; case 0xA779: bufpush(0xA77A); break; case 0xA77B: bufpush(0xA77C); break; case 0xA77D: bufpush(0x1D79); break; case 0xA77E: bufpush(0xA77F); break; case 0xA780: bufpush(0xA781); break; case 0xA782: bufpush(0xA783); break; case 0xA784: bufpush(0xA785); break; case 0xA786: bufpush(0xA787); break; case 0xA78B: bufpush(0xA78C); break; case 0xA78D: bufpush(0x0265); break; case 0xA790: bufpush(0xA791); break; case 0xA792: bufpush(0xA793); break; case 0xA796: bufpush(0xA797); break; case 0xA798: bufpush(0xA799); break; case 0xA79A: bufpush(0xA79B); break; case 0xA79C: bufpush(0xA79D); break; case 0xA79E: bufpush(0xA79F); break; case 0xA7A0: bufpush(0xA7A1); break; case 0xA7A2: bufpush(0xA7A3); break; case 0xA7A4: bufpush(0xA7A5); break; case 0xA7A6: bufpush(0xA7A7); break; case 0xA7A8: bufpush(0xA7A9); break; case 0xA7AA: bufpush(0x0266); break; case 0xA7AB: bufpush(0x025C); break; case 0xA7AC: bufpush(0x0261); break; case 0xA7AD: bufpush(0x026C); break; case 0xA7AE: bufpush(0x026A); break; case 0xA7B0: bufpush(0x029E); break; case 0xA7B1: bufpush(0x0287); break; case 0xA7B2: bufpush(0x029D); break; case 0xA7B3: bufpush(0xAB53); break; case 0xA7B4: bufpush(0xA7B5); break; case 0xA7B6: bufpush(0xA7B7); break; case 0xAB70: bufpush(0x13A0); break; case 0xAB71: bufpush(0x13A1); break; case 0xAB72: bufpush(0x13A2); break; case 0xAB73: bufpush(0x13A3); break; case 0xAB74: bufpush(0x13A4); break; case 0xAB75: bufpush(0x13A5); break; case 0xAB76: bufpush(0x13A6); break; case 0xAB77: bufpush(0x13A7); break; case 0xAB78: bufpush(0x13A8); break; case 0xAB79: bufpush(0x13A9); break; case 0xAB7A: bufpush(0x13AA); break; case 0xAB7B: bufpush(0x13AB); break; case 0xAB7C: bufpush(0x13AC); break; case 0xAB7D: bufpush(0x13AD); break; case 0xAB7E: bufpush(0x13AE); break; case 0xAB7F: bufpush(0x13AF); break; case 0xAB80: bufpush(0x13B0); break; case 0xAB81: bufpush(0x13B1); break; case 0xAB82: bufpush(0x13B2); break; case 0xAB83: bufpush(0x13B3); break; case 0xAB84: bufpush(0x13B4); break; case 0xAB85: bufpush(0x13B5); break; case 0xAB86: bufpush(0x13B6); break; case 0xAB87: bufpush(0x13B7); break; case 0xAB88: bufpush(0x13B8); break; case 0xAB89: bufpush(0x13B9); break; case 0xAB8A: bufpush(0x13BA); break; case 0xAB8B: bufpush(0x13BB); break; case 0xAB8C: bufpush(0x13BC); break; case 0xAB8D: bufpush(0x13BD); break; case 0xAB8E: bufpush(0x13BE); break; case 0xAB8F: bufpush(0x13BF); break; case 0xAB90: bufpush(0x13C0); break; case 0xAB91: bufpush(0x13C1); break; case 0xAB92: bufpush(0x13C2); break; case 0xAB93: bufpush(0x13C3); break; case 0xAB94: bufpush(0x13C4); break; case 0xAB95: bufpush(0x13C5); break; case 0xAB96: bufpush(0x13C6); break; case 0xAB97: bufpush(0x13C7); break; case 0xAB98: bufpush(0x13C8); break; case 0xAB99: bufpush(0x13C9); break; case 0xAB9A: bufpush(0x13CA); break; case 0xAB9B: bufpush(0x13CB); break; case 0xAB9C: bufpush(0x13CC); break; case 0xAB9D: bufpush(0x13CD); break; case 0xAB9E: bufpush(0x13CE); break; case 0xAB9F: bufpush(0x13CF); break; case 0xABA0: bufpush(0x13D0); break; case 0xABA1: bufpush(0x13D1); break; case 0xABA2: bufpush(0x13D2); break; case 0xABA3: bufpush(0x13D3); break; case 0xABA4: bufpush(0x13D4); break; case 0xABA5: bufpush(0x13D5); break; case 0xABA6: bufpush(0x13D6); break; case 0xABA7: bufpush(0x13D7); break; case 0xABA8: bufpush(0x13D8); break; case 0xABA9: bufpush(0x13D9); break; case 0xABAA: bufpush(0x13DA); break; case 0xABAB: bufpush(0x13DB); break; case 0xABAC: bufpush(0x13DC); break; case 0xABAD: bufpush(0x13DD); break; case 0xABAE: bufpush(0x13DE); break; case 0xABAF: bufpush(0x13DF); break; case 0xABB0: bufpush(0x13E0); break; case 0xABB1: bufpush(0x13E1); break; case 0xABB2: bufpush(0x13E2); break; case 0xABB3: bufpush(0x13E3); break; case 0xABB4: bufpush(0x13E4); break; case 0xABB5: bufpush(0x13E5); break; case 0xABB6: bufpush(0x13E6); break; case 0xABB7: bufpush(0x13E7); break; case 0xABB8: bufpush(0x13E8); break; case 0xABB9: bufpush(0x13E9); break; case 0xABBA: bufpush(0x13EA); break; case 0xABBB: bufpush(0x13EB); break; case 0xABBC: bufpush(0x13EC); break; case 0xABBD: bufpush(0x13ED); break; case 0xABBE: bufpush(0x13EE); break; case 0xABBF: bufpush(0x13EF); break; case 0xFB00: bufpush(0x0066); bufpush(0x0066); break; case 0xFB01: bufpush(0x0066); bufpush(0x0069); break; case 0xFB02: bufpush(0x0066); bufpush(0x006C); break; case 0xFB03: bufpush(0x0066); bufpush(0x0066); bufpush(0x0069); break; case 0xFB04: bufpush(0x0066); bufpush(0x0066); bufpush(0x006C); break; case 0xFB05: bufpush(0x0073); bufpush(0x0074); break; case 0xFB06: bufpush(0x0073); bufpush(0x0074); break; case 0xFB13: bufpush(0x0574); bufpush(0x0576); break; case 0xFB14: bufpush(0x0574); bufpush(0x0565); break; case 0xFB15: bufpush(0x0574); bufpush(0x056B); break; case 0xFB16: bufpush(0x057E); bufpush(0x0576); break; case 0xFB17: bufpush(0x0574); bufpush(0x056D); break; case 0xFF21: bufpush(0xFF41); break; case 0xFF22: bufpush(0xFF42); break; case 0xFF23: bufpush(0xFF43); break; case 0xFF24: bufpush(0xFF44); break; case 0xFF25: bufpush(0xFF45); break; case 0xFF26: bufpush(0xFF46); break; case 0xFF27: bufpush(0xFF47); break; case 0xFF28: bufpush(0xFF48); break; case 0xFF29: bufpush(0xFF49); break; case 0xFF2A: bufpush(0xFF4A); break; case 0xFF2B: bufpush(0xFF4B); break; case 0xFF2C: bufpush(0xFF4C); break; case 0xFF2D: bufpush(0xFF4D); break; case 0xFF2E: bufpush(0xFF4E); break; case 0xFF2F: bufpush(0xFF4F); break; case 0xFF30: bufpush(0xFF50); break; case 0xFF31: bufpush(0xFF51); break; case 0xFF32: bufpush(0xFF52); break; case 0xFF33: bufpush(0xFF53); break; case 0xFF34: bufpush(0xFF54); break; case 0xFF35: bufpush(0xFF55); break; case 0xFF36: bufpush(0xFF56); break; case 0xFF37: bufpush(0xFF57); break; case 0xFF38: bufpush(0xFF58); break; case 0xFF39: bufpush(0xFF59); break; case 0xFF3A: bufpush(0xFF5A); break; case 0x10400: bufpush(0x10428); break; case 0x10401: bufpush(0x10429); break; case 0x10402: bufpush(0x1042A); break; case 0x10403: bufpush(0x1042B); break; case 0x10404: bufpush(0x1042C); break; case 0x10405: bufpush(0x1042D); break; case 0x10406: bufpush(0x1042E); break; case 0x10407: bufpush(0x1042F); break; case 0x10408: bufpush(0x10430); break; case 0x10409: bufpush(0x10431); break; case 0x1040A: bufpush(0x10432); break; case 0x1040B: bufpush(0x10433); break; case 0x1040C: bufpush(0x10434); break; case 0x1040D: bufpush(0x10435); break; case 0x1040E: bufpush(0x10436); break; case 0x1040F: bufpush(0x10437); break; case 0x10410: bufpush(0x10438); break; case 0x10411: bufpush(0x10439); break; case 0x10412: bufpush(0x1043A); break; case 0x10413: bufpush(0x1043B); break; case 0x10414: bufpush(0x1043C); break; case 0x10415: bufpush(0x1043D); break; case 0x10416: bufpush(0x1043E); break; case 0x10417: bufpush(0x1043F); break; case 0x10418: bufpush(0x10440); break; case 0x10419: bufpush(0x10441); break; case 0x1041A: bufpush(0x10442); break; case 0x1041B: bufpush(0x10443); break; case 0x1041C: bufpush(0x10444); break; case 0x1041D: bufpush(0x10445); break; case 0x1041E: bufpush(0x10446); break; case 0x1041F: bufpush(0x10447); break; case 0x10420: bufpush(0x10448); break; case 0x10421: bufpush(0x10449); break; case 0x10422: bufpush(0x1044A); break; case 0x10423: bufpush(0x1044B); break; case 0x10424: bufpush(0x1044C); break; case 0x10425: bufpush(0x1044D); break; case 0x10426: bufpush(0x1044E); break; case 0x10427: bufpush(0x1044F); break; case 0x104B0: bufpush(0x104D8); break; case 0x104B1: bufpush(0x104D9); break; case 0x104B2: bufpush(0x104DA); break; case 0x104B3: bufpush(0x104DB); break; case 0x104B4: bufpush(0x104DC); break; case 0x104B5: bufpush(0x104DD); break; case 0x104B6: bufpush(0x104DE); break; case 0x104B7: bufpush(0x104DF); break; case 0x104B8: bufpush(0x104E0); break; case 0x104B9: bufpush(0x104E1); break; case 0x104BA: bufpush(0x104E2); break; case 0x104BB: bufpush(0x104E3); break; case 0x104BC: bufpush(0x104E4); break; case 0x104BD: bufpush(0x104E5); break; case 0x104BE: bufpush(0x104E6); break; case 0x104BF: bufpush(0x104E7); break; case 0x104C0: bufpush(0x104E8); break; case 0x104C1: bufpush(0x104E9); break; case 0x104C2: bufpush(0x104EA); break; case 0x104C3: bufpush(0x104EB); break; case 0x104C4: bufpush(0x104EC); break; case 0x104C5: bufpush(0x104ED); break; case 0x104C6: bufpush(0x104EE); break; case 0x104C7: bufpush(0x104EF); break; case 0x104C8: bufpush(0x104F0); break; case 0x104C9: bufpush(0x104F1); break; case 0x104CA: bufpush(0x104F2); break; case 0x104CB: bufpush(0x104F3); break; case 0x104CC: bufpush(0x104F4); break; case 0x104CD: bufpush(0x104F5); break; case 0x104CE: bufpush(0x104F6); break; case 0x104CF: bufpush(0x104F7); break; case 0x104D0: bufpush(0x104F8); break; case 0x104D1: bufpush(0x104F9); break; case 0x104D2: bufpush(0x104FA); break; case 0x104D3: bufpush(0x104FB); break; case 0x10C80: bufpush(0x10CC0); break; case 0x10C81: bufpush(0x10CC1); break; case 0x10C82: bufpush(0x10CC2); break; case 0x10C83: bufpush(0x10CC3); break; case 0x10C84: bufpush(0x10CC4); break; case 0x10C85: bufpush(0x10CC5); break; case 0x10C86: bufpush(0x10CC6); break; case 0x10C87: bufpush(0x10CC7); break; case 0x10C88: bufpush(0x10CC8); break; case 0x10C89: bufpush(0x10CC9); break; case 0x10C8A: bufpush(0x10CCA); break; case 0x10C8B: bufpush(0x10CCB); break; case 0x10C8C: bufpush(0x10CCC); break; case 0x10C8D: bufpush(0x10CCD); break; case 0x10C8E: bufpush(0x10CCE); break; case 0x10C8F: bufpush(0x10CCF); break; case 0x10C90: bufpush(0x10CD0); break; case 0x10C91: bufpush(0x10CD1); break; case 0x10C92: bufpush(0x10CD2); break; case 0x10C93: bufpush(0x10CD3); break; case 0x10C94: bufpush(0x10CD4); break; case 0x10C95: bufpush(0x10CD5); break; case 0x10C96: bufpush(0x10CD6); break; case 0x10C97: bufpush(0x10CD7); break; case 0x10C98: bufpush(0x10CD8); break; case 0x10C99: bufpush(0x10CD9); break; case 0x10C9A: bufpush(0x10CDA); break; case 0x10C9B: bufpush(0x10CDB); break; case 0x10C9C: bufpush(0x10CDC); break; case 0x10C9D: bufpush(0x10CDD); break; case 0x10C9E: bufpush(0x10CDE); break; case 0x10C9F: bufpush(0x10CDF); break; case 0x10CA0: bufpush(0x10CE0); break; case 0x10CA1: bufpush(0x10CE1); break; case 0x10CA2: bufpush(0x10CE2); break; case 0x10CA3: bufpush(0x10CE3); break; case 0x10CA4: bufpush(0x10CE4); break; case 0x10CA5: bufpush(0x10CE5); break; case 0x10CA6: bufpush(0x10CE6); break; case 0x10CA7: bufpush(0x10CE7); break; case 0x10CA8: bufpush(0x10CE8); break; case 0x10CA9: bufpush(0x10CE9); break; case 0x10CAA: bufpush(0x10CEA); break; case 0x10CAB: bufpush(0x10CEB); break; case 0x10CAC: bufpush(0x10CEC); break; case 0x10CAD: bufpush(0x10CED); break; case 0x10CAE: bufpush(0x10CEE); break; case 0x10CAF: bufpush(0x10CEF); break; case 0x10CB0: bufpush(0x10CF0); break; case 0x10CB1: bufpush(0x10CF1); break; case 0x10CB2: bufpush(0x10CF2); break; case 0x118A0: bufpush(0x118C0); break; case 0x118A1: bufpush(0x118C1); break; case 0x118A2: bufpush(0x118C2); break; case 0x118A3: bufpush(0x118C3); break; case 0x118A4: bufpush(0x118C4); break; case 0x118A5: bufpush(0x118C5); break; case 0x118A6: bufpush(0x118C6); break; case 0x118A7: bufpush(0x118C7); break; case 0x118A8: bufpush(0x118C8); break; case 0x118A9: bufpush(0x118C9); break; case 0x118AA: bufpush(0x118CA); break; case 0x118AB: bufpush(0x118CB); break; case 0x118AC: bufpush(0x118CC); break; case 0x118AD: bufpush(0x118CD); break; case 0x118AE: bufpush(0x118CE); break; case 0x118AF: bufpush(0x118CF); break; case 0x118B0: bufpush(0x118D0); break; case 0x118B1: bufpush(0x118D1); break; case 0x118B2: bufpush(0x118D2); break; case 0x118B3: bufpush(0x118D3); break; case 0x118B4: bufpush(0x118D4); break; case 0x118B5: bufpush(0x118D5); break; case 0x118B6: bufpush(0x118D6); break; case 0x118B7: bufpush(0x118D7); break; case 0x118B8: bufpush(0x118D8); break; case 0x118B9: bufpush(0x118D9); break; case 0x118BA: bufpush(0x118DA); break; case 0x118BB: bufpush(0x118DB); break; case 0x118BC: bufpush(0x118DC); break; case 0x118BD: bufpush(0x118DD); break; case 0x118BE: bufpush(0x118DE); break; case 0x118BF: bufpush(0x118DF); break; case 0x1E900: bufpush(0x1E922); break; case 0x1E901: bufpush(0x1E923); break; case 0x1E902: bufpush(0x1E924); break; case 0x1E903: bufpush(0x1E925); break; case 0x1E904: bufpush(0x1E926); break; case 0x1E905: bufpush(0x1E927); break; case 0x1E906: bufpush(0x1E928); break; case 0x1E907: bufpush(0x1E929); break; case 0x1E908: bufpush(0x1E92A); break; case 0x1E909: bufpush(0x1E92B); break; case 0x1E90A: bufpush(0x1E92C); break; case 0x1E90B: bufpush(0x1E92D); break; case 0x1E90C: bufpush(0x1E92E); break; case 0x1E90D: bufpush(0x1E92F); break; case 0x1E90E: bufpush(0x1E930); break; case 0x1E90F: bufpush(0x1E931); break; case 0x1E910: bufpush(0x1E932); break; case 0x1E911: bufpush(0x1E933); break; case 0x1E912: bufpush(0x1E934); break; case 0x1E913: bufpush(0x1E935); break; case 0x1E914: bufpush(0x1E936); break; case 0x1E915: bufpush(0x1E937); break; case 0x1E916: bufpush(0x1E938); break; case 0x1E917: bufpush(0x1E939); break; case 0x1E918: bufpush(0x1E93A); break; case 0x1E919: bufpush(0x1E93B); break; case 0x1E91A: bufpush(0x1E93C); break; case 0x1E91B: bufpush(0x1E93D); break; case 0x1E91C: bufpush(0x1E93E); break; case 0x1E91D: bufpush(0x1E93F); break; case 0x1E91E: bufpush(0x1E940); break; case 0x1E91F: bufpush(0x1E941); break; case 0x1E920: bufpush(0x1E942); break; case 0x1E921: bufpush(0x1E943); break; default: bufpush(c); } �����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/entities.inc������������������������������������������������������������������0000644�0000000�0000000�00000310476�13336672520�015217� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������/* Autogenerated by tools/make_headers_inc.py */ struct cmark_entity_node { unsigned char *entity; unsigned char bytes[8]; }; #define CMARK_ENTITY_MIN_LENGTH 2 #define CMARK_ENTITY_MAX_LENGTH 32 #define CMARK_NUM_ENTITIES 2125 static const struct cmark_entity_node cmark_entities[] = { {(unsigned char*)"AElig", {195, 134, 0}}, {(unsigned char*)"AMP", {38, 0}}, {(unsigned char*)"Aacute", {195, 129, 0}}, {(unsigned char*)"Abreve", {196, 130, 0}}, {(unsigned char*)"Acirc", {195, 130, 0}}, {(unsigned char*)"Acy", {208, 144, 0}}, {(unsigned char*)"Afr", {240, 157, 148, 132, 0}}, {(unsigned char*)"Agrave", {195, 128, 0}}, {(unsigned char*)"Alpha", {206, 145, 0}}, {(unsigned char*)"Amacr", {196, 128, 0}}, {(unsigned char*)"And", {226, 169, 147, 0}}, {(unsigned char*)"Aogon", {196, 132, 0}}, {(unsigned char*)"Aopf", {240, 157, 148, 184, 0}}, {(unsigned char*)"ApplyFunction", {226, 129, 161, 0}}, {(unsigned char*)"Aring", {195, 133, 0}}, {(unsigned char*)"Ascr", {240, 157, 146, 156, 0}}, {(unsigned char*)"Assign", {226, 137, 148, 0}}, {(unsigned char*)"Atilde", {195, 131, 0}}, {(unsigned char*)"Auml", {195, 132, 0}}, {(unsigned char*)"Backslash", {226, 136, 150, 0}}, {(unsigned char*)"Barv", {226, 171, 167, 0}}, {(unsigned char*)"Barwed", {226, 140, 134, 0}}, {(unsigned char*)"Bcy", {208, 145, 0}}, {(unsigned char*)"Because", {226, 136, 181, 0}}, {(unsigned char*)"Bernoullis", {226, 132, 172, 0}}, {(unsigned char*)"Beta", {206, 146, 0}}, {(unsigned char*)"Bfr", {240, 157, 148, 133, 0}}, {(unsigned char*)"Bopf", {240, 157, 148, 185, 0}}, {(unsigned char*)"Breve", {203, 152, 0}}, {(unsigned char*)"Bscr", {226, 132, 172, 0}}, {(unsigned char*)"Bumpeq", {226, 137, 142, 0}}, {(unsigned char*)"CHcy", {208, 167, 0}}, {(unsigned char*)"COPY", {194, 169, 0}}, {(unsigned char*)"Cacute", {196, 134, 0}}, {(unsigned char*)"Cap", {226, 139, 146, 0}}, {(unsigned char*)"CapitalDifferentialD", {226, 133, 133, 0}}, {(unsigned char*)"Cayleys", {226, 132, 173, 0}}, {(unsigned char*)"Ccaron", {196, 140, 0}}, {(unsigned char*)"Ccedil", {195, 135, 0}}, {(unsigned char*)"Ccirc", {196, 136, 0}}, {(unsigned char*)"Cconint", {226, 136, 176, 0}}, {(unsigned char*)"Cdot", {196, 138, 0}}, {(unsigned char*)"Cedilla", {194, 184, 0}}, {(unsigned char*)"CenterDot", {194, 183, 0}}, {(unsigned char*)"Cfr", {226, 132, 173, 0}}, {(unsigned char*)"Chi", {206, 167, 0}}, {(unsigned char*)"CircleDot", {226, 138, 153, 0}}, {(unsigned char*)"CircleMinus", {226, 138, 150, 0}}, {(unsigned char*)"CirclePlus", {226, 138, 149, 0}}, {(unsigned char*)"CircleTimes", {226, 138, 151, 0}}, {(unsigned char*)"ClockwiseContourIntegral", {226, 136, 178, 0}}, {(unsigned char*)"CloseCurlyDoubleQuote", {226, 128, 157, 0}}, {(unsigned char*)"CloseCurlyQuote", {226, 128, 153, 0}}, {(unsigned char*)"Colon", {226, 136, 183, 0}}, {(unsigned char*)"Colone", {226, 169, 180, 0}}, {(unsigned char*)"Congruent", {226, 137, 161, 0}}, {(unsigned char*)"Conint", {226, 136, 175, 0}}, {(unsigned char*)"ContourIntegral", {226, 136, 174, 0}}, {(unsigned char*)"Copf", {226, 132, 130, 0}}, {(unsigned char*)"Coproduct", {226, 136, 144, 0}}, {(unsigned char*)"CounterClockwiseContourIntegral", {226, 136, 179, 0}}, {(unsigned char*)"Cross", {226, 168, 175, 0}}, {(unsigned char*)"Cscr", {240, 157, 146, 158, 0}}, {(unsigned char*)"Cup", {226, 139, 147, 0}}, {(unsigned char*)"CupCap", {226, 137, 141, 0}}, {(unsigned char*)"DD", {226, 133, 133, 0}}, {(unsigned char*)"DDotrahd", {226, 164, 145, 0}}, {(unsigned char*)"DJcy", {208, 130, 0}}, {(unsigned char*)"DScy", {208, 133, 0}}, {(unsigned char*)"DZcy", {208, 143, 0}}, {(unsigned char*)"Dagger", {226, 128, 161, 0}}, {(unsigned char*)"Darr", {226, 134, 161, 0}}, {(unsigned char*)"Dashv", {226, 171, 164, 0}}, {(unsigned char*)"Dcaron", {196, 142, 0}}, {(unsigned char*)"Dcy", {208, 148, 0}}, {(unsigned char*)"Del", {226, 136, 135, 0}}, {(unsigned char*)"Delta", {206, 148, 0}}, {(unsigned char*)"Dfr", {240, 157, 148, 135, 0}}, {(unsigned char*)"DiacriticalAcute", {194, 180, 0}}, {(unsigned char*)"DiacriticalDot", {203, 153, 0}}, {(unsigned char*)"DiacriticalDoubleAcute", {203, 157, 0}}, {(unsigned char*)"DiacriticalGrave", {96, 0}}, {(unsigned char*)"DiacriticalTilde", {203, 156, 0}}, {(unsigned char*)"Diamond", {226, 139, 132, 0}}, {(unsigned char*)"DifferentialD", {226, 133, 134, 0}}, {(unsigned char*)"Dopf", {240, 157, 148, 187, 0}}, {(unsigned char*)"Dot", {194, 168, 0}}, {(unsigned char*)"DotDot", {226, 131, 156, 0}}, {(unsigned char*)"DotEqual", {226, 137, 144, 0}}, {(unsigned char*)"DoubleContourIntegral", {226, 136, 175, 0}}, {(unsigned char*)"DoubleDot", {194, 168, 0}}, {(unsigned char*)"DoubleDownArrow", {226, 135, 147, 0}}, {(unsigned char*)"DoubleLeftArrow", {226, 135, 144, 0}}, {(unsigned char*)"DoubleLeftRightArrow", {226, 135, 148, 0}}, {(unsigned char*)"DoubleLeftTee", {226, 171, 164, 0}}, {(unsigned char*)"DoubleLongLeftArrow", {226, 159, 184, 0}}, {(unsigned char*)"DoubleLongLeftRightArrow", {226, 159, 186, 0}}, {(unsigned char*)"DoubleLongRightArrow", {226, 159, 185, 0}}, {(unsigned char*)"DoubleRightArrow", {226, 135, 146, 0}}, {(unsigned char*)"DoubleRightTee", {226, 138, 168, 0}}, {(unsigned char*)"DoubleUpArrow", {226, 135, 145, 0}}, {(unsigned char*)"DoubleUpDownArrow", {226, 135, 149, 0}}, {(unsigned char*)"DoubleVerticalBar", {226, 136, 165, 0}}, {(unsigned char*)"DownArrow", {226, 134, 147, 0}}, {(unsigned char*)"DownArrowBar", {226, 164, 147, 0}}, {(unsigned char*)"DownArrowUpArrow", {226, 135, 181, 0}}, {(unsigned char*)"DownBreve", {204, 145, 0}}, {(unsigned char*)"DownLeftRightVector", {226, 165, 144, 0}}, {(unsigned char*)"DownLeftTeeVector", {226, 165, 158, 0}}, {(unsigned char*)"DownLeftVector", {226, 134, 189, 0}}, {(unsigned char*)"DownLeftVectorBar", {226, 165, 150, 0}}, {(unsigned char*)"DownRightTeeVector", {226, 165, 159, 0}}, {(unsigned char*)"DownRightVector", {226, 135, 129, 0}}, {(unsigned char*)"DownRightVectorBar", {226, 165, 151, 0}}, {(unsigned char*)"DownTee", {226, 138, 164, 0}}, {(unsigned char*)"DownTeeArrow", {226, 134, 167, 0}}, {(unsigned char*)"Downarrow", {226, 135, 147, 0}}, {(unsigned char*)"Dscr", {240, 157, 146, 159, 0}}, {(unsigned char*)"Dstrok", {196, 144, 0}}, {(unsigned char*)"ENG", {197, 138, 0}}, {(unsigned char*)"ETH", {195, 144, 0}}, {(unsigned char*)"Eacute", {195, 137, 0}}, {(unsigned char*)"Ecaron", {196, 154, 0}}, {(unsigned char*)"Ecirc", {195, 138, 0}}, {(unsigned char*)"Ecy", {208, 173, 0}}, {(unsigned char*)"Edot", {196, 150, 0}}, {(unsigned char*)"Efr", {240, 157, 148, 136, 0}}, {(unsigned char*)"Egrave", {195, 136, 0}}, {(unsigned char*)"Element", {226, 136, 136, 0}}, {(unsigned char*)"Emacr", {196, 146, 0}}, {(unsigned char*)"EmptySmallSquare", {226, 151, 187, 0}}, {(unsigned char*)"EmptyVerySmallSquare", {226, 150, 171, 0}}, {(unsigned char*)"Eogon", {196, 152, 0}}, {(unsigned char*)"Eopf", {240, 157, 148, 188, 0}}, {(unsigned char*)"Epsilon", {206, 149, 0}}, {(unsigned char*)"Equal", {226, 169, 181, 0}}, {(unsigned char*)"EqualTilde", {226, 137, 130, 0}}, {(unsigned char*)"Equilibrium", {226, 135, 140, 0}}, {(unsigned char*)"Escr", {226, 132, 176, 0}}, {(unsigned char*)"Esim", {226, 169, 179, 0}}, {(unsigned char*)"Eta", {206, 151, 0}}, {(unsigned char*)"Euml", {195, 139, 0}}, {(unsigned char*)"Exists", {226, 136, 131, 0}}, {(unsigned char*)"ExponentialE", {226, 133, 135, 0}}, {(unsigned char*)"Fcy", {208, 164, 0}}, {(unsigned char*)"Ffr", {240, 157, 148, 137, 0}}, {(unsigned char*)"FilledSmallSquare", {226, 151, 188, 0}}, {(unsigned char*)"FilledVerySmallSquare", {226, 150, 170, 0}}, {(unsigned char*)"Fopf", {240, 157, 148, 189, 0}}, {(unsigned char*)"ForAll", {226, 136, 128, 0}}, {(unsigned char*)"Fouriertrf", {226, 132, 177, 0}}, {(unsigned char*)"Fscr", {226, 132, 177, 0}}, {(unsigned char*)"GJcy", {208, 131, 0}}, {(unsigned char*)"GT", {62, 0}}, {(unsigned char*)"Gamma", {206, 147, 0}}, {(unsigned char*)"Gammad", {207, 156, 0}}, {(unsigned char*)"Gbreve", {196, 158, 0}}, {(unsigned char*)"Gcedil", {196, 162, 0}}, {(unsigned char*)"Gcirc", {196, 156, 0}}, {(unsigned char*)"Gcy", {208, 147, 0}}, {(unsigned char*)"Gdot", {196, 160, 0}}, {(unsigned char*)"Gfr", {240, 157, 148, 138, 0}}, {(unsigned char*)"Gg", {226, 139, 153, 0}}, {(unsigned char*)"Gopf", {240, 157, 148, 190, 0}}, {(unsigned char*)"GreaterEqual", {226, 137, 165, 0}}, {(unsigned char*)"GreaterEqualLess", {226, 139, 155, 0}}, {(unsigned char*)"GreaterFullEqual", {226, 137, 167, 0}}, {(unsigned char*)"GreaterGreater", {226, 170, 162, 0}}, {(unsigned char*)"GreaterLess", {226, 137, 183, 0}}, {(unsigned char*)"GreaterSlantEqual", {226, 169, 190, 0}}, {(unsigned char*)"GreaterTilde", {226, 137, 179, 0}}, {(unsigned char*)"Gscr", {240, 157, 146, 162, 0}}, {(unsigned char*)"Gt", {226, 137, 171, 0}}, {(unsigned char*)"HARDcy", {208, 170, 0}}, {(unsigned char*)"Hacek", {203, 135, 0}}, {(unsigned char*)"Hat", {94, 0}}, {(unsigned char*)"Hcirc", {196, 164, 0}}, {(unsigned char*)"Hfr", {226, 132, 140, 0}}, {(unsigned char*)"HilbertSpace", {226, 132, 139, 0}}, {(unsigned char*)"Hopf", {226, 132, 141, 0}}, {(unsigned char*)"HorizontalLine", {226, 148, 128, 0}}, {(unsigned char*)"Hscr", {226, 132, 139, 0}}, {(unsigned char*)"Hstrok", {196, 166, 0}}, {(unsigned char*)"HumpDownHump", {226, 137, 142, 0}}, {(unsigned char*)"HumpEqual", {226, 137, 143, 0}}, {(unsigned char*)"IEcy", {208, 149, 0}}, {(unsigned char*)"IJlig", {196, 178, 0}}, {(unsigned char*)"IOcy", {208, 129, 0}}, {(unsigned char*)"Iacute", {195, 141, 0}}, {(unsigned char*)"Icirc", {195, 142, 0}}, {(unsigned char*)"Icy", {208, 152, 0}}, {(unsigned char*)"Idot", {196, 176, 0}}, {(unsigned char*)"Ifr", {226, 132, 145, 0}}, {(unsigned char*)"Igrave", {195, 140, 0}}, {(unsigned char*)"Im", {226, 132, 145, 0}}, {(unsigned char*)"Imacr", {196, 170, 0}}, {(unsigned char*)"ImaginaryI", {226, 133, 136, 0}}, {(unsigned char*)"Implies", {226, 135, 146, 0}}, {(unsigned char*)"Int", {226, 136, 172, 0}}, {(unsigned char*)"Integral", {226, 136, 171, 0}}, {(unsigned char*)"Intersection", {226, 139, 130, 0}}, {(unsigned char*)"InvisibleComma", {226, 129, 163, 0}}, {(unsigned char*)"InvisibleTimes", {226, 129, 162, 0}}, {(unsigned char*)"Iogon", {196, 174, 0}}, {(unsigned char*)"Iopf", {240, 157, 149, 128, 0}}, {(unsigned char*)"Iota", {206, 153, 0}}, {(unsigned char*)"Iscr", {226, 132, 144, 0}}, {(unsigned char*)"Itilde", {196, 168, 0}}, {(unsigned char*)"Iukcy", {208, 134, 0}}, {(unsigned char*)"Iuml", {195, 143, 0}}, {(unsigned char*)"Jcirc", {196, 180, 0}}, {(unsigned char*)"Jcy", {208, 153, 0}}, {(unsigned char*)"Jfr", {240, 157, 148, 141, 0}}, {(unsigned char*)"Jopf", {240, 157, 149, 129, 0}}, {(unsigned char*)"Jscr", {240, 157, 146, 165, 0}}, {(unsigned char*)"Jsercy", {208, 136, 0}}, {(unsigned char*)"Jukcy", {208, 132, 0}}, {(unsigned char*)"KHcy", {208, 165, 0}}, {(unsigned char*)"KJcy", {208, 140, 0}}, {(unsigned char*)"Kappa", {206, 154, 0}}, {(unsigned char*)"Kcedil", {196, 182, 0}}, {(unsigned char*)"Kcy", {208, 154, 0}}, {(unsigned char*)"Kfr", {240, 157, 148, 142, 0}}, {(unsigned char*)"Kopf", {240, 157, 149, 130, 0}}, {(unsigned char*)"Kscr", {240, 157, 146, 166, 0}}, {(unsigned char*)"LJcy", {208, 137, 0}}, {(unsigned char*)"LT", {60, 0}}, {(unsigned char*)"Lacute", {196, 185, 0}}, {(unsigned char*)"Lambda", {206, 155, 0}}, {(unsigned char*)"Lang", {226, 159, 170, 0}}, {(unsigned char*)"Laplacetrf", {226, 132, 146, 0}}, {(unsigned char*)"Larr", {226, 134, 158, 0}}, {(unsigned char*)"Lcaron", {196, 189, 0}}, {(unsigned char*)"Lcedil", {196, 187, 0}}, {(unsigned char*)"Lcy", {208, 155, 0}}, {(unsigned char*)"LeftAngleBracket", {226, 159, 168, 0}}, {(unsigned char*)"LeftArrow", {226, 134, 144, 0}}, {(unsigned char*)"LeftArrowBar", {226, 135, 164, 0}}, {(unsigned char*)"LeftArrowRightArrow", {226, 135, 134, 0}}, {(unsigned char*)"LeftCeiling", {226, 140, 136, 0}}, {(unsigned char*)"LeftDoubleBracket", {226, 159, 166, 0}}, {(unsigned char*)"LeftDownTeeVector", {226, 165, 161, 0}}, {(unsigned char*)"LeftDownVector", {226, 135, 131, 0}}, {(unsigned char*)"LeftDownVectorBar", {226, 165, 153, 0}}, {(unsigned char*)"LeftFloor", {226, 140, 138, 0}}, {(unsigned char*)"LeftRightArrow", {226, 134, 148, 0}}, {(unsigned char*)"LeftRightVector", {226, 165, 142, 0}}, {(unsigned char*)"LeftTee", {226, 138, 163, 0}}, {(unsigned char*)"LeftTeeArrow", {226, 134, 164, 0}}, {(unsigned char*)"LeftTeeVector", {226, 165, 154, 0}}, {(unsigned char*)"LeftTriangle", {226, 138, 178, 0}}, {(unsigned char*)"LeftTriangleBar", {226, 167, 143, 0}}, {(unsigned char*)"LeftTriangleEqual", {226, 138, 180, 0}}, {(unsigned char*)"LeftUpDownVector", {226, 165, 145, 0}}, {(unsigned char*)"LeftUpTeeVector", {226, 165, 160, 0}}, {(unsigned char*)"LeftUpVector", {226, 134, 191, 0}}, {(unsigned char*)"LeftUpVectorBar", {226, 165, 152, 0}}, {(unsigned char*)"LeftVector", {226, 134, 188, 0}}, {(unsigned char*)"LeftVectorBar", {226, 165, 146, 0}}, {(unsigned char*)"Leftarrow", {226, 135, 144, 0}}, {(unsigned char*)"Leftrightarrow", {226, 135, 148, 0}}, {(unsigned char*)"LessEqualGreater", {226, 139, 154, 0}}, {(unsigned char*)"LessFullEqual", {226, 137, 166, 0}}, {(unsigned char*)"LessGreater", {226, 137, 182, 0}}, {(unsigned char*)"LessLess", {226, 170, 161, 0}}, {(unsigned char*)"LessSlantEqual", {226, 169, 189, 0}}, {(unsigned char*)"LessTilde", {226, 137, 178, 0}}, {(unsigned char*)"Lfr", {240, 157, 148, 143, 0}}, {(unsigned char*)"Ll", {226, 139, 152, 0}}, {(unsigned char*)"Lleftarrow", {226, 135, 154, 0}}, {(unsigned char*)"Lmidot", {196, 191, 0}}, {(unsigned char*)"LongLeftArrow", {226, 159, 181, 0}}, {(unsigned char*)"LongLeftRightArrow", {226, 159, 183, 0}}, {(unsigned char*)"LongRightArrow", {226, 159, 182, 0}}, {(unsigned char*)"Longleftarrow", {226, 159, 184, 0}}, {(unsigned char*)"Longleftrightarrow", {226, 159, 186, 0}}, {(unsigned char*)"Longrightarrow", {226, 159, 185, 0}}, {(unsigned char*)"Lopf", {240, 157, 149, 131, 0}}, {(unsigned char*)"LowerLeftArrow", {226, 134, 153, 0}}, {(unsigned char*)"LowerRightArrow", {226, 134, 152, 0}}, {(unsigned char*)"Lscr", {226, 132, 146, 0}}, {(unsigned char*)"Lsh", {226, 134, 176, 0}}, {(unsigned char*)"Lstrok", {197, 129, 0}}, {(unsigned char*)"Lt", {226, 137, 170, 0}}, {(unsigned char*)"Map", {226, 164, 133, 0}}, {(unsigned char*)"Mcy", {208, 156, 0}}, {(unsigned char*)"MediumSpace", {226, 129, 159, 0}}, {(unsigned char*)"Mellintrf", {226, 132, 179, 0}}, {(unsigned char*)"Mfr", {240, 157, 148, 144, 0}}, {(unsigned char*)"MinusPlus", {226, 136, 147, 0}}, {(unsigned char*)"Mopf", {240, 157, 149, 132, 0}}, {(unsigned char*)"Mscr", {226, 132, 179, 0}}, {(unsigned char*)"Mu", {206, 156, 0}}, {(unsigned char*)"NJcy", {208, 138, 0}}, {(unsigned char*)"Nacute", {197, 131, 0}}, {(unsigned char*)"Ncaron", {197, 135, 0}}, {(unsigned char*)"Ncedil", {197, 133, 0}}, {(unsigned char*)"Ncy", {208, 157, 0}}, {(unsigned char*)"NegativeMediumSpace", {226, 128, 139, 0}}, {(unsigned char*)"NegativeThickSpace", {226, 128, 139, 0}}, {(unsigned char*)"NegativeThinSpace", {226, 128, 139, 0}}, {(unsigned char*)"NegativeVeryThinSpace", {226, 128, 139, 0}}, {(unsigned char*)"NestedGreaterGreater", {226, 137, 171, 0}}, {(unsigned char*)"NestedLessLess", {226, 137, 170, 0}}, {(unsigned char*)"NewLine", {10, 0}}, {(unsigned char*)"Nfr", {240, 157, 148, 145, 0}}, {(unsigned char*)"NoBreak", {226, 129, 160, 0}}, {(unsigned char*)"NonBreakingSpace", {194, 160, 0}}, {(unsigned char*)"Nopf", {226, 132, 149, 0}}, {(unsigned char*)"Not", {226, 171, 172, 0}}, {(unsigned char*)"NotCongruent", {226, 137, 162, 0}}, {(unsigned char*)"NotCupCap", {226, 137, 173, 0}}, {(unsigned char*)"NotDoubleVerticalBar", {226, 136, 166, 0}}, {(unsigned char*)"NotElement", {226, 136, 137, 0}}, {(unsigned char*)"NotEqual", {226, 137, 160, 0}}, {(unsigned char*)"NotEqualTilde", {226, 137, 130, 204, 184, 0}}, {(unsigned char*)"NotExists", {226, 136, 132, 0}}, {(unsigned char*)"NotGreater", {226, 137, 175, 0}}, {(unsigned char*)"NotGreaterEqual", {226, 137, 177, 0}}, {(unsigned char*)"NotGreaterFullEqual", {226, 137, 167, 204, 184, 0}}, {(unsigned char*)"NotGreaterGreater", {226, 137, 171, 204, 184, 0}}, {(unsigned char*)"NotGreaterLess", {226, 137, 185, 0}}, {(unsigned char*)"NotGreaterSlantEqual", {226, 169, 190, 204, 184, 0}}, {(unsigned char*)"NotGreaterTilde", {226, 137, 181, 0}}, {(unsigned char*)"NotHumpDownHump", {226, 137, 142, 204, 184, 0}}, {(unsigned char*)"NotHumpEqual", {226, 137, 143, 204, 184, 0}}, {(unsigned char*)"NotLeftTriangle", {226, 139, 170, 0}}, {(unsigned char*)"NotLeftTriangleBar", {226, 167, 143, 204, 184, 0}}, {(unsigned char*)"NotLeftTriangleEqual", {226, 139, 172, 0}}, {(unsigned char*)"NotLess", {226, 137, 174, 0}}, {(unsigned char*)"NotLessEqual", {226, 137, 176, 0}}, {(unsigned char*)"NotLessGreater", {226, 137, 184, 0}}, {(unsigned char*)"NotLessLess", {226, 137, 170, 204, 184, 0}}, {(unsigned char*)"NotLessSlantEqual", {226, 169, 189, 204, 184, 0}}, {(unsigned char*)"NotLessTilde", {226, 137, 180, 0}}, {(unsigned char*)"NotNestedGreaterGreater", {226, 170, 162, 204, 184, 0}}, {(unsigned char*)"NotNestedLessLess", {226, 170, 161, 204, 184, 0}}, {(unsigned char*)"NotPrecedes", {226, 138, 128, 0}}, {(unsigned char*)"NotPrecedesEqual", {226, 170, 175, 204, 184, 0}}, {(unsigned char*)"NotPrecedesSlantEqual", {226, 139, 160, 0}}, {(unsigned char*)"NotReverseElement", {226, 136, 140, 0}}, {(unsigned char*)"NotRightTriangle", {226, 139, 171, 0}}, {(unsigned char*)"NotRightTriangleBar", {226, 167, 144, 204, 184, 0}}, {(unsigned char*)"NotRightTriangleEqual", {226, 139, 173, 0}}, {(unsigned char*)"NotSquareSubset", {226, 138, 143, 204, 184, 0}}, {(unsigned char*)"NotSquareSubsetEqual", {226, 139, 162, 0}}, {(unsigned char*)"NotSquareSuperset", {226, 138, 144, 204, 184, 0}}, {(unsigned char*)"NotSquareSupersetEqual", {226, 139, 163, 0}}, {(unsigned char*)"NotSubset", {226, 138, 130, 226, 131, 146, 0}}, {(unsigned char*)"NotSubsetEqual", {226, 138, 136, 0}}, {(unsigned char*)"NotSucceeds", {226, 138, 129, 0}}, {(unsigned char*)"NotSucceedsEqual", {226, 170, 176, 204, 184, 0}}, {(unsigned char*)"NotSucceedsSlantEqual", {226, 139, 161, 0}}, {(unsigned char*)"NotSucceedsTilde", {226, 137, 191, 204, 184, 0}}, {(unsigned char*)"NotSuperset", {226, 138, 131, 226, 131, 146, 0}}, {(unsigned char*)"NotSupersetEqual", {226, 138, 137, 0}}, {(unsigned char*)"NotTilde", {226, 137, 129, 0}}, {(unsigned char*)"NotTildeEqual", {226, 137, 132, 0}}, {(unsigned char*)"NotTildeFullEqual", {226, 137, 135, 0}}, {(unsigned char*)"NotTildeTilde", {226, 137, 137, 0}}, {(unsigned char*)"NotVerticalBar", {226, 136, 164, 0}}, {(unsigned char*)"Nscr", {240, 157, 146, 169, 0}}, {(unsigned char*)"Ntilde", {195, 145, 0}}, {(unsigned char*)"Nu", {206, 157, 0}}, {(unsigned char*)"OElig", {197, 146, 0}}, {(unsigned char*)"Oacute", {195, 147, 0}}, {(unsigned char*)"Ocirc", {195, 148, 0}}, {(unsigned char*)"Ocy", {208, 158, 0}}, {(unsigned char*)"Odblac", {197, 144, 0}}, {(unsigned char*)"Ofr", {240, 157, 148, 146, 0}}, {(unsigned char*)"Ograve", {195, 146, 0}}, {(unsigned char*)"Omacr", {197, 140, 0}}, {(unsigned char*)"Omega", {206, 169, 0}}, {(unsigned char*)"Omicron", {206, 159, 0}}, {(unsigned char*)"Oopf", {240, 157, 149, 134, 0}}, {(unsigned char*)"OpenCurlyDoubleQuote", {226, 128, 156, 0}}, {(unsigned char*)"OpenCurlyQuote", {226, 128, 152, 0}}, {(unsigned char*)"Or", {226, 169, 148, 0}}, {(unsigned char*)"Oscr", {240, 157, 146, 170, 0}}, {(unsigned char*)"Oslash", {195, 152, 0}}, {(unsigned char*)"Otilde", {195, 149, 0}}, {(unsigned char*)"Otimes", {226, 168, 183, 0}}, {(unsigned char*)"Ouml", {195, 150, 0}}, {(unsigned char*)"OverBar", {226, 128, 190, 0}}, {(unsigned char*)"OverBrace", {226, 143, 158, 0}}, {(unsigned char*)"OverBracket", {226, 142, 180, 0}}, {(unsigned char*)"OverParenthesis", {226, 143, 156, 0}}, {(unsigned char*)"PartialD", {226, 136, 130, 0}}, {(unsigned char*)"Pcy", {208, 159, 0}}, {(unsigned char*)"Pfr", {240, 157, 148, 147, 0}}, {(unsigned char*)"Phi", {206, 166, 0}}, {(unsigned char*)"Pi", {206, 160, 0}}, {(unsigned char*)"PlusMinus", {194, 177, 0}}, {(unsigned char*)"Poincareplane", {226, 132, 140, 0}}, {(unsigned char*)"Popf", {226, 132, 153, 0}}, {(unsigned char*)"Pr", {226, 170, 187, 0}}, {(unsigned char*)"Precedes", {226, 137, 186, 0}}, {(unsigned char*)"PrecedesEqual", {226, 170, 175, 0}}, {(unsigned char*)"PrecedesSlantEqual", {226, 137, 188, 0}}, {(unsigned char*)"PrecedesTilde", {226, 137, 190, 0}}, {(unsigned char*)"Prime", {226, 128, 179, 0}}, {(unsigned char*)"Product", {226, 136, 143, 0}}, {(unsigned char*)"Proportion", {226, 136, 183, 0}}, {(unsigned char*)"Proportional", {226, 136, 157, 0}}, {(unsigned char*)"Pscr", {240, 157, 146, 171, 0}}, {(unsigned char*)"Psi", {206, 168, 0}}, {(unsigned char*)"QUOT", {34, 0}}, {(unsigned char*)"Qfr", {240, 157, 148, 148, 0}}, {(unsigned char*)"Qopf", {226, 132, 154, 0}}, {(unsigned char*)"Qscr", {240, 157, 146, 172, 0}}, {(unsigned char*)"RBarr", {226, 164, 144, 0}}, {(unsigned char*)"REG", {194, 174, 0}}, {(unsigned char*)"Racute", {197, 148, 0}}, {(unsigned char*)"Rang", {226, 159, 171, 0}}, {(unsigned char*)"Rarr", {226, 134, 160, 0}}, {(unsigned char*)"Rarrtl", {226, 164, 150, 0}}, {(unsigned char*)"Rcaron", {197, 152, 0}}, {(unsigned char*)"Rcedil", {197, 150, 0}}, {(unsigned char*)"Rcy", {208, 160, 0}}, {(unsigned char*)"Re", {226, 132, 156, 0}}, {(unsigned char*)"ReverseElement", {226, 136, 139, 0}}, {(unsigned char*)"ReverseEquilibrium", {226, 135, 139, 0}}, {(unsigned char*)"ReverseUpEquilibrium", {226, 165, 175, 0}}, {(unsigned char*)"Rfr", {226, 132, 156, 0}}, {(unsigned char*)"Rho", {206, 161, 0}}, {(unsigned char*)"RightAngleBracket", {226, 159, 169, 0}}, {(unsigned char*)"RightArrow", {226, 134, 146, 0}}, {(unsigned char*)"RightArrowBar", {226, 135, 165, 0}}, {(unsigned char*)"RightArrowLeftArrow", {226, 135, 132, 0}}, {(unsigned char*)"RightCeiling", {226, 140, 137, 0}}, {(unsigned char*)"RightDoubleBracket", {226, 159, 167, 0}}, {(unsigned char*)"RightDownTeeVector", {226, 165, 157, 0}}, {(unsigned char*)"RightDownVector", {226, 135, 130, 0}}, {(unsigned char*)"RightDownVectorBar", {226, 165, 149, 0}}, {(unsigned char*)"RightFloor", {226, 140, 139, 0}}, {(unsigned char*)"RightTee", {226, 138, 162, 0}}, {(unsigned char*)"RightTeeArrow", {226, 134, 166, 0}}, {(unsigned char*)"RightTeeVector", {226, 165, 155, 0}}, {(unsigned char*)"RightTriangle", {226, 138, 179, 0}}, {(unsigned char*)"RightTriangleBar", {226, 167, 144, 0}}, {(unsigned char*)"RightTriangleEqual", {226, 138, 181, 0}}, {(unsigned char*)"RightUpDownVector", {226, 165, 143, 0}}, {(unsigned char*)"RightUpTeeVector", {226, 165, 156, 0}}, {(unsigned char*)"RightUpVector", {226, 134, 190, 0}}, {(unsigned char*)"RightUpVectorBar", {226, 165, 148, 0}}, {(unsigned char*)"RightVector", {226, 135, 128, 0}}, {(unsigned char*)"RightVectorBar", {226, 165, 147, 0}}, {(unsigned char*)"Rightarrow", {226, 135, 146, 0}}, {(unsigned char*)"Ropf", {226, 132, 157, 0}}, {(unsigned char*)"RoundImplies", {226, 165, 176, 0}}, {(unsigned char*)"Rrightarrow", {226, 135, 155, 0}}, {(unsigned char*)"Rscr", {226, 132, 155, 0}}, {(unsigned char*)"Rsh", {226, 134, 177, 0}}, {(unsigned char*)"RuleDelayed", {226, 167, 180, 0}}, {(unsigned char*)"SHCHcy", {208, 169, 0}}, {(unsigned char*)"SHcy", {208, 168, 0}}, {(unsigned char*)"SOFTcy", {208, 172, 0}}, {(unsigned char*)"Sacute", {197, 154, 0}}, {(unsigned char*)"Sc", {226, 170, 188, 0}}, {(unsigned char*)"Scaron", {197, 160, 0}}, {(unsigned char*)"Scedil", {197, 158, 0}}, {(unsigned char*)"Scirc", {197, 156, 0}}, {(unsigned char*)"Scy", {208, 161, 0}}, {(unsigned char*)"Sfr", {240, 157, 148, 150, 0}}, {(unsigned char*)"ShortDownArrow", {226, 134, 147, 0}}, {(unsigned char*)"ShortLeftArrow", {226, 134, 144, 0}}, {(unsigned char*)"ShortRightArrow", {226, 134, 146, 0}}, {(unsigned char*)"ShortUpArrow", {226, 134, 145, 0}}, {(unsigned char*)"Sigma", {206, 163, 0}}, {(unsigned char*)"SmallCircle", {226, 136, 152, 0}}, {(unsigned char*)"Sopf", {240, 157, 149, 138, 0}}, {(unsigned char*)"Sqrt", {226, 136, 154, 0}}, {(unsigned char*)"Square", {226, 150, 161, 0}}, {(unsigned char*)"SquareIntersection", {226, 138, 147, 0}}, {(unsigned char*)"SquareSubset", {226, 138, 143, 0}}, {(unsigned char*)"SquareSubsetEqual", {226, 138, 145, 0}}, {(unsigned char*)"SquareSuperset", {226, 138, 144, 0}}, {(unsigned char*)"SquareSupersetEqual", {226, 138, 146, 0}}, {(unsigned char*)"SquareUnion", {226, 138, 148, 0}}, {(unsigned char*)"Sscr", {240, 157, 146, 174, 0}}, {(unsigned char*)"Star", {226, 139, 134, 0}}, {(unsigned char*)"Sub", {226, 139, 144, 0}}, {(unsigned char*)"Subset", {226, 139, 144, 0}}, {(unsigned char*)"SubsetEqual", {226, 138, 134, 0}}, {(unsigned char*)"Succeeds", {226, 137, 187, 0}}, {(unsigned char*)"SucceedsEqual", {226, 170, 176, 0}}, {(unsigned char*)"SucceedsSlantEqual", {226, 137, 189, 0}}, {(unsigned char*)"SucceedsTilde", {226, 137, 191, 0}}, {(unsigned char*)"SuchThat", {226, 136, 139, 0}}, {(unsigned char*)"Sum", {226, 136, 145, 0}}, {(unsigned char*)"Sup", {226, 139, 145, 0}}, {(unsigned char*)"Superset", {226, 138, 131, 0}}, {(unsigned char*)"SupersetEqual", {226, 138, 135, 0}}, {(unsigned char*)"Supset", {226, 139, 145, 0}}, {(unsigned char*)"THORN", {195, 158, 0}}, {(unsigned char*)"TRADE", {226, 132, 162, 0}}, {(unsigned char*)"TSHcy", {208, 139, 0}}, {(unsigned char*)"TScy", {208, 166, 0}}, {(unsigned char*)"Tab", {9, 0}}, {(unsigned char*)"Tau", {206, 164, 0}}, {(unsigned char*)"Tcaron", {197, 164, 0}}, {(unsigned char*)"Tcedil", {197, 162, 0}}, {(unsigned char*)"Tcy", {208, 162, 0}}, {(unsigned char*)"Tfr", {240, 157, 148, 151, 0}}, {(unsigned char*)"Therefore", {226, 136, 180, 0}}, {(unsigned char*)"Theta", {206, 152, 0}}, {(unsigned char*)"ThickSpace", {226, 129, 159, 226, 128, 138, 0}}, {(unsigned char*)"ThinSpace", {226, 128, 137, 0}}, {(unsigned char*)"Tilde", {226, 136, 188, 0}}, {(unsigned char*)"TildeEqual", {226, 137, 131, 0}}, {(unsigned char*)"TildeFullEqual", {226, 137, 133, 0}}, {(unsigned char*)"TildeTilde", {226, 137, 136, 0}}, {(unsigned char*)"Topf", {240, 157, 149, 139, 0}}, {(unsigned char*)"TripleDot", {226, 131, 155, 0}}, {(unsigned char*)"Tscr", {240, 157, 146, 175, 0}}, {(unsigned char*)"Tstrok", {197, 166, 0}}, {(unsigned char*)"Uacute", {195, 154, 0}}, {(unsigned char*)"Uarr", {226, 134, 159, 0}}, {(unsigned char*)"Uarrocir", {226, 165, 137, 0}}, {(unsigned char*)"Ubrcy", {208, 142, 0}}, {(unsigned char*)"Ubreve", {197, 172, 0}}, {(unsigned char*)"Ucirc", {195, 155, 0}}, {(unsigned char*)"Ucy", {208, 163, 0}}, {(unsigned char*)"Udblac", {197, 176, 0}}, {(unsigned char*)"Ufr", {240, 157, 148, 152, 0}}, {(unsigned char*)"Ugrave", {195, 153, 0}}, {(unsigned char*)"Umacr", {197, 170, 0}}, {(unsigned char*)"UnderBar", {95, 0}}, {(unsigned char*)"UnderBrace", {226, 143, 159, 0}}, {(unsigned char*)"UnderBracket", {226, 142, 181, 0}}, {(unsigned char*)"UnderParenthesis", {226, 143, 157, 0}}, {(unsigned char*)"Union", {226, 139, 131, 0}}, {(unsigned char*)"UnionPlus", {226, 138, 142, 0}}, {(unsigned char*)"Uogon", {197, 178, 0}}, {(unsigned char*)"Uopf", {240, 157, 149, 140, 0}}, {(unsigned char*)"UpArrow", {226, 134, 145, 0}}, {(unsigned char*)"UpArrowBar", {226, 164, 146, 0}}, {(unsigned char*)"UpArrowDownArrow", {226, 135, 133, 0}}, {(unsigned char*)"UpDownArrow", {226, 134, 149, 0}}, {(unsigned char*)"UpEquilibrium", {226, 165, 174, 0}}, {(unsigned char*)"UpTee", {226, 138, 165, 0}}, {(unsigned char*)"UpTeeArrow", {226, 134, 165, 0}}, {(unsigned char*)"Uparrow", {226, 135, 145, 0}}, {(unsigned char*)"Updownarrow", {226, 135, 149, 0}}, {(unsigned char*)"UpperLeftArrow", {226, 134, 150, 0}}, {(unsigned char*)"UpperRightArrow", {226, 134, 151, 0}}, {(unsigned char*)"Upsi", {207, 146, 0}}, {(unsigned char*)"Upsilon", {206, 165, 0}}, {(unsigned char*)"Uring", {197, 174, 0}}, {(unsigned char*)"Uscr", {240, 157, 146, 176, 0}}, {(unsigned char*)"Utilde", {197, 168, 0}}, {(unsigned char*)"Uuml", {195, 156, 0}}, {(unsigned char*)"VDash", {226, 138, 171, 0}}, {(unsigned char*)"Vbar", {226, 171, 171, 0}}, {(unsigned char*)"Vcy", {208, 146, 0}}, {(unsigned char*)"Vdash", {226, 138, 169, 0}}, {(unsigned char*)"Vdashl", {226, 171, 166, 0}}, {(unsigned char*)"Vee", {226, 139, 129, 0}}, {(unsigned char*)"Verbar", {226, 128, 150, 0}}, {(unsigned char*)"Vert", {226, 128, 150, 0}}, {(unsigned char*)"VerticalBar", {226, 136, 163, 0}}, {(unsigned char*)"VerticalLine", {124, 0}}, {(unsigned char*)"VerticalSeparator", {226, 157, 152, 0}}, {(unsigned char*)"VerticalTilde", {226, 137, 128, 0}}, {(unsigned char*)"VeryThinSpace", {226, 128, 138, 0}}, {(unsigned char*)"Vfr", {240, 157, 148, 153, 0}}, {(unsigned char*)"Vopf", {240, 157, 149, 141, 0}}, {(unsigned char*)"Vscr", {240, 157, 146, 177, 0}}, {(unsigned char*)"Vvdash", {226, 138, 170, 0}}, {(unsigned char*)"Wcirc", {197, 180, 0}}, {(unsigned char*)"Wedge", {226, 139, 128, 0}}, {(unsigned char*)"Wfr", {240, 157, 148, 154, 0}}, {(unsigned char*)"Wopf", {240, 157, 149, 142, 0}}, {(unsigned char*)"Wscr", {240, 157, 146, 178, 0}}, {(unsigned char*)"Xfr", {240, 157, 148, 155, 0}}, {(unsigned char*)"Xi", {206, 158, 0}}, {(unsigned char*)"Xopf", {240, 157, 149, 143, 0}}, {(unsigned char*)"Xscr", {240, 157, 146, 179, 0}}, {(unsigned char*)"YAcy", {208, 175, 0}}, {(unsigned char*)"YIcy", {208, 135, 0}}, {(unsigned char*)"YUcy", {208, 174, 0}}, {(unsigned char*)"Yacute", {195, 157, 0}}, {(unsigned char*)"Ycirc", {197, 182, 0}}, {(unsigned char*)"Ycy", {208, 171, 0}}, {(unsigned char*)"Yfr", {240, 157, 148, 156, 0}}, {(unsigned char*)"Yopf", {240, 157, 149, 144, 0}}, {(unsigned char*)"Yscr", {240, 157, 146, 180, 0}}, {(unsigned char*)"Yuml", {197, 184, 0}}, {(unsigned char*)"ZHcy", {208, 150, 0}}, {(unsigned char*)"Zacute", {197, 185, 0}}, {(unsigned char*)"Zcaron", {197, 189, 0}}, {(unsigned char*)"Zcy", {208, 151, 0}}, {(unsigned char*)"Zdot", {197, 187, 0}}, {(unsigned char*)"ZeroWidthSpace", {226, 128, 139, 0}}, {(unsigned char*)"Zeta", {206, 150, 0}}, {(unsigned char*)"Zfr", {226, 132, 168, 0}}, {(unsigned char*)"Zopf", {226, 132, 164, 0}}, {(unsigned char*)"Zscr", {240, 157, 146, 181, 0}}, {(unsigned char*)"aacute", {195, 161, 0}}, {(unsigned char*)"abreve", {196, 131, 0}}, {(unsigned char*)"ac", {226, 136, 190, 0}}, {(unsigned char*)"acE", {226, 136, 190, 204, 179, 0}}, {(unsigned char*)"acd", {226, 136, 191, 0}}, {(unsigned char*)"acirc", {195, 162, 0}}, {(unsigned char*)"acute", {194, 180, 0}}, {(unsigned char*)"acy", {208, 176, 0}}, {(unsigned char*)"aelig", {195, 166, 0}}, {(unsigned char*)"af", {226, 129, 161, 0}}, {(unsigned char*)"afr", {240, 157, 148, 158, 0}}, {(unsigned char*)"agrave", {195, 160, 0}}, {(unsigned char*)"alefsym", {226, 132, 181, 0}}, {(unsigned char*)"aleph", {226, 132, 181, 0}}, {(unsigned char*)"alpha", {206, 177, 0}}, {(unsigned char*)"amacr", {196, 129, 0}}, {(unsigned char*)"amalg", {226, 168, 191, 0}}, {(unsigned char*)"amp", {38, 0}}, {(unsigned char*)"and", {226, 136, 167, 0}}, {(unsigned char*)"andand", {226, 169, 149, 0}}, {(unsigned char*)"andd", {226, 169, 156, 0}}, {(unsigned char*)"andslope", {226, 169, 152, 0}}, {(unsigned char*)"andv", {226, 169, 154, 0}}, {(unsigned char*)"ang", {226, 136, 160, 0}}, {(unsigned char*)"ange", {226, 166, 164, 0}}, {(unsigned char*)"angle", {226, 136, 160, 0}}, {(unsigned char*)"angmsd", {226, 136, 161, 0}}, {(unsigned char*)"angmsdaa", {226, 166, 168, 0}}, {(unsigned char*)"angmsdab", {226, 166, 169, 0}}, {(unsigned char*)"angmsdac", {226, 166, 170, 0}}, {(unsigned char*)"angmsdad", {226, 166, 171, 0}}, {(unsigned char*)"angmsdae", {226, 166, 172, 0}}, {(unsigned char*)"angmsdaf", {226, 166, 173, 0}}, {(unsigned char*)"angmsdag", {226, 166, 174, 0}}, {(unsigned char*)"angmsdah", {226, 166, 175, 0}}, {(unsigned char*)"angrt", {226, 136, 159, 0}}, {(unsigned char*)"angrtvb", {226, 138, 190, 0}}, {(unsigned char*)"angrtvbd", {226, 166, 157, 0}}, {(unsigned char*)"angsph", {226, 136, 162, 0}}, {(unsigned char*)"angst", {195, 133, 0}}, {(unsigned char*)"angzarr", {226, 141, 188, 0}}, {(unsigned char*)"aogon", {196, 133, 0}}, {(unsigned char*)"aopf", {240, 157, 149, 146, 0}}, {(unsigned char*)"ap", {226, 137, 136, 0}}, {(unsigned char*)"apE", {226, 169, 176, 0}}, {(unsigned char*)"apacir", {226, 169, 175, 0}}, {(unsigned char*)"ape", {226, 137, 138, 0}}, {(unsigned char*)"apid", {226, 137, 139, 0}}, {(unsigned char*)"apos", {39, 0}}, {(unsigned char*)"approx", {226, 137, 136, 0}}, {(unsigned char*)"approxeq", {226, 137, 138, 0}}, {(unsigned char*)"aring", {195, 165, 0}}, {(unsigned char*)"ascr", {240, 157, 146, 182, 0}}, {(unsigned char*)"ast", {42, 0}}, {(unsigned char*)"asymp", {226, 137, 136, 0}}, {(unsigned char*)"asympeq", {226, 137, 141, 0}}, {(unsigned char*)"atilde", {195, 163, 0}}, {(unsigned char*)"auml", {195, 164, 0}}, {(unsigned char*)"awconint", {226, 136, 179, 0}}, {(unsigned char*)"awint", {226, 168, 145, 0}}, {(unsigned char*)"bNot", {226, 171, 173, 0}}, {(unsigned char*)"backcong", {226, 137, 140, 0}}, {(unsigned char*)"backepsilon", {207, 182, 0}}, {(unsigned char*)"backprime", {226, 128, 181, 0}}, {(unsigned char*)"backsim", {226, 136, 189, 0}}, {(unsigned char*)"backsimeq", {226, 139, 141, 0}}, {(unsigned char*)"barvee", {226, 138, 189, 0}}, {(unsigned char*)"barwed", {226, 140, 133, 0}}, {(unsigned char*)"barwedge", {226, 140, 133, 0}}, {(unsigned char*)"bbrk", {226, 142, 181, 0}}, {(unsigned char*)"bbrktbrk", {226, 142, 182, 0}}, {(unsigned char*)"bcong", {226, 137, 140, 0}}, {(unsigned char*)"bcy", {208, 177, 0}}, {(unsigned char*)"bdquo", {226, 128, 158, 0}}, {(unsigned char*)"becaus", {226, 136, 181, 0}}, {(unsigned char*)"because", {226, 136, 181, 0}}, {(unsigned char*)"bemptyv", {226, 166, 176, 0}}, {(unsigned char*)"bepsi", {207, 182, 0}}, {(unsigned char*)"bernou", {226, 132, 172, 0}}, {(unsigned char*)"beta", {206, 178, 0}}, {(unsigned char*)"beth", {226, 132, 182, 0}}, {(unsigned char*)"between", {226, 137, 172, 0}}, {(unsigned char*)"bfr", {240, 157, 148, 159, 0}}, {(unsigned char*)"bigcap", {226, 139, 130, 0}}, {(unsigned char*)"bigcirc", {226, 151, 175, 0}}, {(unsigned char*)"bigcup", {226, 139, 131, 0}}, {(unsigned char*)"bigodot", {226, 168, 128, 0}}, {(unsigned char*)"bigoplus", {226, 168, 129, 0}}, {(unsigned char*)"bigotimes", {226, 168, 130, 0}}, {(unsigned char*)"bigsqcup", {226, 168, 134, 0}}, {(unsigned char*)"bigstar", {226, 152, 133, 0}}, {(unsigned char*)"bigtriangledown", {226, 150, 189, 0}}, {(unsigned char*)"bigtriangleup", {226, 150, 179, 0}}, {(unsigned char*)"biguplus", {226, 168, 132, 0}}, {(unsigned char*)"bigvee", {226, 139, 129, 0}}, {(unsigned char*)"bigwedge", {226, 139, 128, 0}}, {(unsigned char*)"bkarow", {226, 164, 141, 0}}, {(unsigned char*)"blacklozenge", {226, 167, 171, 0}}, {(unsigned char*)"blacksquare", {226, 150, 170, 0}}, {(unsigned char*)"blacktriangle", {226, 150, 180, 0}}, {(unsigned char*)"blacktriangledown", {226, 150, 190, 0}}, {(unsigned char*)"blacktriangleleft", {226, 151, 130, 0}}, {(unsigned char*)"blacktriangleright", {226, 150, 184, 0}}, {(unsigned char*)"blank", {226, 144, 163, 0}}, {(unsigned char*)"blk12", {226, 150, 146, 0}}, {(unsigned char*)"blk14", {226, 150, 145, 0}}, {(unsigned char*)"blk34", {226, 150, 147, 0}}, {(unsigned char*)"block", {226, 150, 136, 0}}, {(unsigned char*)"bne", {61, 226, 131, 165, 0}}, {(unsigned char*)"bnequiv", {226, 137, 161, 226, 131, 165, 0}}, {(unsigned char*)"bnot", {226, 140, 144, 0}}, {(unsigned char*)"bopf", {240, 157, 149, 147, 0}}, {(unsigned char*)"bot", {226, 138, 165, 0}}, {(unsigned char*)"bottom", {226, 138, 165, 0}}, {(unsigned char*)"bowtie", {226, 139, 136, 0}}, {(unsigned char*)"boxDL", {226, 149, 151, 0}}, {(unsigned char*)"boxDR", {226, 149, 148, 0}}, {(unsigned char*)"boxDl", {226, 149, 150, 0}}, {(unsigned char*)"boxDr", {226, 149, 147, 0}}, {(unsigned char*)"boxH", {226, 149, 144, 0}}, {(unsigned char*)"boxHD", {226, 149, 166, 0}}, {(unsigned char*)"boxHU", {226, 149, 169, 0}}, {(unsigned char*)"boxHd", {226, 149, 164, 0}}, {(unsigned char*)"boxHu", {226, 149, 167, 0}}, {(unsigned char*)"boxUL", {226, 149, 157, 0}}, {(unsigned char*)"boxUR", {226, 149, 154, 0}}, {(unsigned char*)"boxUl", {226, 149, 156, 0}}, {(unsigned char*)"boxUr", {226, 149, 153, 0}}, {(unsigned char*)"boxV", {226, 149, 145, 0}}, {(unsigned char*)"boxVH", {226, 149, 172, 0}}, {(unsigned char*)"boxVL", {226, 149, 163, 0}}, {(unsigned char*)"boxVR", {226, 149, 160, 0}}, {(unsigned char*)"boxVh", {226, 149, 171, 0}}, {(unsigned char*)"boxVl", {226, 149, 162, 0}}, {(unsigned char*)"boxVr", {226, 149, 159, 0}}, {(unsigned char*)"boxbox", {226, 167, 137, 0}}, {(unsigned char*)"boxdL", {226, 149, 149, 0}}, {(unsigned char*)"boxdR", {226, 149, 146, 0}}, {(unsigned char*)"boxdl", {226, 148, 144, 0}}, {(unsigned char*)"boxdr", {226, 148, 140, 0}}, {(unsigned char*)"boxh", {226, 148, 128, 0}}, {(unsigned char*)"boxhD", {226, 149, 165, 0}}, {(unsigned char*)"boxhU", {226, 149, 168, 0}}, {(unsigned char*)"boxhd", {226, 148, 172, 0}}, {(unsigned char*)"boxhu", {226, 148, 180, 0}}, {(unsigned char*)"boxminus", {226, 138, 159, 0}}, {(unsigned char*)"boxplus", {226, 138, 158, 0}}, {(unsigned char*)"boxtimes", {226, 138, 160, 0}}, {(unsigned char*)"boxuL", {226, 149, 155, 0}}, {(unsigned char*)"boxuR", {226, 149, 152, 0}}, {(unsigned char*)"boxul", {226, 148, 152, 0}}, {(unsigned char*)"boxur", {226, 148, 148, 0}}, {(unsigned char*)"boxv", {226, 148, 130, 0}}, {(unsigned char*)"boxvH", {226, 149, 170, 0}}, {(unsigned char*)"boxvL", {226, 149, 161, 0}}, {(unsigned char*)"boxvR", {226, 149, 158, 0}}, {(unsigned char*)"boxvh", {226, 148, 188, 0}}, {(unsigned char*)"boxvl", {226, 148, 164, 0}}, {(unsigned char*)"boxvr", {226, 148, 156, 0}}, {(unsigned char*)"bprime", {226, 128, 181, 0}}, {(unsigned char*)"breve", {203, 152, 0}}, {(unsigned char*)"brvbar", {194, 166, 0}}, {(unsigned char*)"bscr", {240, 157, 146, 183, 0}}, {(unsigned char*)"bsemi", {226, 129, 143, 0}}, {(unsigned char*)"bsim", {226, 136, 189, 0}}, {(unsigned char*)"bsime", {226, 139, 141, 0}}, {(unsigned char*)"bsol", {92, 0}}, {(unsigned char*)"bsolb", {226, 167, 133, 0}}, {(unsigned char*)"bsolhsub", {226, 159, 136, 0}}, {(unsigned char*)"bull", {226, 128, 162, 0}}, {(unsigned char*)"bullet", {226, 128, 162, 0}}, {(unsigned char*)"bump", {226, 137, 142, 0}}, {(unsigned char*)"bumpE", {226, 170, 174, 0}}, {(unsigned char*)"bumpe", {226, 137, 143, 0}}, {(unsigned char*)"bumpeq", {226, 137, 143, 0}}, {(unsigned char*)"cacute", {196, 135, 0}}, {(unsigned char*)"cap", {226, 136, 169, 0}}, {(unsigned char*)"capand", {226, 169, 132, 0}}, {(unsigned char*)"capbrcup", {226, 169, 137, 0}}, {(unsigned char*)"capcap", {226, 169, 139, 0}}, {(unsigned char*)"capcup", {226, 169, 135, 0}}, {(unsigned char*)"capdot", {226, 169, 128, 0}}, {(unsigned char*)"caps", {226, 136, 169, 239, 184, 128, 0}}, {(unsigned char*)"caret", {226, 129, 129, 0}}, {(unsigned char*)"caron", {203, 135, 0}}, {(unsigned char*)"ccaps", {226, 169, 141, 0}}, {(unsigned char*)"ccaron", {196, 141, 0}}, {(unsigned char*)"ccedil", {195, 167, 0}}, {(unsigned char*)"ccirc", {196, 137, 0}}, {(unsigned char*)"ccups", {226, 169, 140, 0}}, {(unsigned char*)"ccupssm", {226, 169, 144, 0}}, {(unsigned char*)"cdot", {196, 139, 0}}, {(unsigned char*)"cedil", {194, 184, 0}}, {(unsigned char*)"cemptyv", {226, 166, 178, 0}}, {(unsigned char*)"cent", {194, 162, 0}}, {(unsigned char*)"centerdot", {194, 183, 0}}, {(unsigned char*)"cfr", {240, 157, 148, 160, 0}}, {(unsigned char*)"chcy", {209, 135, 0}}, {(unsigned char*)"check", {226, 156, 147, 0}}, {(unsigned char*)"checkmark", {226, 156, 147, 0}}, {(unsigned char*)"chi", {207, 135, 0}}, {(unsigned char*)"cir", {226, 151, 139, 0}}, {(unsigned char*)"cirE", {226, 167, 131, 0}}, {(unsigned char*)"circ", {203, 134, 0}}, {(unsigned char*)"circeq", {226, 137, 151, 0}}, {(unsigned char*)"circlearrowleft", {226, 134, 186, 0}}, {(unsigned char*)"circlearrowright", {226, 134, 187, 0}}, {(unsigned char*)"circledR", {194, 174, 0}}, {(unsigned char*)"circledS", {226, 147, 136, 0}}, {(unsigned char*)"circledast", {226, 138, 155, 0}}, {(unsigned char*)"circledcirc", {226, 138, 154, 0}}, {(unsigned char*)"circleddash", {226, 138, 157, 0}}, {(unsigned char*)"cire", {226, 137, 151, 0}}, {(unsigned char*)"cirfnint", {226, 168, 144, 0}}, {(unsigned char*)"cirmid", {226, 171, 175, 0}}, {(unsigned char*)"cirscir", {226, 167, 130, 0}}, {(unsigned char*)"clubs", {226, 153, 163, 0}}, {(unsigned char*)"clubsuit", {226, 153, 163, 0}}, {(unsigned char*)"colon", {58, 0}}, {(unsigned char*)"colone", {226, 137, 148, 0}}, {(unsigned char*)"coloneq", {226, 137, 148, 0}}, {(unsigned char*)"comma", {44, 0}}, {(unsigned char*)"commat", {64, 0}}, {(unsigned char*)"comp", {226, 136, 129, 0}}, {(unsigned char*)"compfn", {226, 136, 152, 0}}, {(unsigned char*)"complement", {226, 136, 129, 0}}, {(unsigned char*)"complexes", {226, 132, 130, 0}}, {(unsigned char*)"cong", {226, 137, 133, 0}}, {(unsigned char*)"congdot", {226, 169, 173, 0}}, {(unsigned char*)"conint", {226, 136, 174, 0}}, {(unsigned char*)"copf", {240, 157, 149, 148, 0}}, {(unsigned char*)"coprod", {226, 136, 144, 0}}, {(unsigned char*)"copy", {194, 169, 0}}, {(unsigned char*)"copysr", {226, 132, 151, 0}}, {(unsigned char*)"crarr", {226, 134, 181, 0}}, {(unsigned char*)"cross", {226, 156, 151, 0}}, {(unsigned char*)"cscr", {240, 157, 146, 184, 0}}, {(unsigned char*)"csub", {226, 171, 143, 0}}, {(unsigned char*)"csube", {226, 171, 145, 0}}, {(unsigned char*)"csup", {226, 171, 144, 0}}, {(unsigned char*)"csupe", {226, 171, 146, 0}}, {(unsigned char*)"ctdot", {226, 139, 175, 0}}, {(unsigned char*)"cudarrl", {226, 164, 184, 0}}, {(unsigned char*)"cudarrr", {226, 164, 181, 0}}, {(unsigned char*)"cuepr", {226, 139, 158, 0}}, {(unsigned char*)"cuesc", {226, 139, 159, 0}}, {(unsigned char*)"cularr", {226, 134, 182, 0}}, {(unsigned char*)"cularrp", {226, 164, 189, 0}}, {(unsigned char*)"cup", {226, 136, 170, 0}}, {(unsigned char*)"cupbrcap", {226, 169, 136, 0}}, {(unsigned char*)"cupcap", {226, 169, 134, 0}}, {(unsigned char*)"cupcup", {226, 169, 138, 0}}, {(unsigned char*)"cupdot", {226, 138, 141, 0}}, {(unsigned char*)"cupor", {226, 169, 133, 0}}, {(unsigned char*)"cups", {226, 136, 170, 239, 184, 128, 0}}, {(unsigned char*)"curarr", {226, 134, 183, 0}}, {(unsigned char*)"curarrm", {226, 164, 188, 0}}, {(unsigned char*)"curlyeqprec", {226, 139, 158, 0}}, {(unsigned char*)"curlyeqsucc", {226, 139, 159, 0}}, {(unsigned char*)"curlyvee", {226, 139, 142, 0}}, {(unsigned char*)"curlywedge", {226, 139, 143, 0}}, {(unsigned char*)"curren", {194, 164, 0}}, {(unsigned char*)"curvearrowleft", {226, 134, 182, 0}}, {(unsigned char*)"curvearrowright", {226, 134, 183, 0}}, {(unsigned char*)"cuvee", {226, 139, 142, 0}}, {(unsigned char*)"cuwed", {226, 139, 143, 0}}, {(unsigned char*)"cwconint", {226, 136, 178, 0}}, {(unsigned char*)"cwint", {226, 136, 177, 0}}, {(unsigned char*)"cylcty", {226, 140, 173, 0}}, {(unsigned char*)"dArr", {226, 135, 147, 0}}, {(unsigned char*)"dHar", {226, 165, 165, 0}}, {(unsigned char*)"dagger", {226, 128, 160, 0}}, {(unsigned char*)"daleth", {226, 132, 184, 0}}, {(unsigned char*)"darr", {226, 134, 147, 0}}, {(unsigned char*)"dash", {226, 128, 144, 0}}, {(unsigned char*)"dashv", {226, 138, 163, 0}}, {(unsigned char*)"dbkarow", {226, 164, 143, 0}}, {(unsigned char*)"dblac", {203, 157, 0}}, {(unsigned char*)"dcaron", {196, 143, 0}}, {(unsigned char*)"dcy", {208, 180, 0}}, {(unsigned char*)"dd", {226, 133, 134, 0}}, {(unsigned char*)"ddagger", {226, 128, 161, 0}}, {(unsigned char*)"ddarr", {226, 135, 138, 0}}, {(unsigned char*)"ddotseq", {226, 169, 183, 0}}, {(unsigned char*)"deg", {194, 176, 0}}, {(unsigned char*)"delta", {206, 180, 0}}, {(unsigned char*)"demptyv", {226, 166, 177, 0}}, {(unsigned char*)"dfisht", {226, 165, 191, 0}}, {(unsigned char*)"dfr", {240, 157, 148, 161, 0}}, {(unsigned char*)"dharl", {226, 135, 131, 0}}, {(unsigned char*)"dharr", {226, 135, 130, 0}}, {(unsigned char*)"diam", {226, 139, 132, 0}}, {(unsigned char*)"diamond", {226, 139, 132, 0}}, {(unsigned char*)"diamondsuit", {226, 153, 166, 0}}, {(unsigned char*)"diams", {226, 153, 166, 0}}, {(unsigned char*)"die", {194, 168, 0}}, {(unsigned char*)"digamma", {207, 157, 0}}, {(unsigned char*)"disin", {226, 139, 178, 0}}, {(unsigned char*)"div", {195, 183, 0}}, {(unsigned char*)"divide", {195, 183, 0}}, {(unsigned char*)"divideontimes", {226, 139, 135, 0}}, {(unsigned char*)"divonx", {226, 139, 135, 0}}, {(unsigned char*)"djcy", {209, 146, 0}}, {(unsigned char*)"dlcorn", {226, 140, 158, 0}}, {(unsigned char*)"dlcrop", {226, 140, 141, 0}}, {(unsigned char*)"dollar", {36, 0}}, {(unsigned char*)"dopf", {240, 157, 149, 149, 0}}, {(unsigned char*)"dot", {203, 153, 0}}, {(unsigned char*)"doteq", {226, 137, 144, 0}}, {(unsigned char*)"doteqdot", {226, 137, 145, 0}}, {(unsigned char*)"dotminus", {226, 136, 184, 0}}, {(unsigned char*)"dotplus", {226, 136, 148, 0}}, {(unsigned char*)"dotsquare", {226, 138, 161, 0}}, {(unsigned char*)"doublebarwedge", {226, 140, 134, 0}}, {(unsigned char*)"downarrow", {226, 134, 147, 0}}, {(unsigned char*)"downdownarrows", {226, 135, 138, 0}}, {(unsigned char*)"downharpoonleft", {226, 135, 131, 0}}, {(unsigned char*)"downharpoonright", {226, 135, 130, 0}}, {(unsigned char*)"drbkarow", {226, 164, 144, 0}}, {(unsigned char*)"drcorn", {226, 140, 159, 0}}, {(unsigned char*)"drcrop", {226, 140, 140, 0}}, {(unsigned char*)"dscr", {240, 157, 146, 185, 0}}, {(unsigned char*)"dscy", {209, 149, 0}}, {(unsigned char*)"dsol", {226, 167, 182, 0}}, {(unsigned char*)"dstrok", {196, 145, 0}}, {(unsigned char*)"dtdot", {226, 139, 177, 0}}, {(unsigned char*)"dtri", {226, 150, 191, 0}}, {(unsigned char*)"dtrif", {226, 150, 190, 0}}, {(unsigned char*)"duarr", {226, 135, 181, 0}}, {(unsigned char*)"duhar", {226, 165, 175, 0}}, {(unsigned char*)"dwangle", {226, 166, 166, 0}}, {(unsigned char*)"dzcy", {209, 159, 0}}, {(unsigned char*)"dzigrarr", {226, 159, 191, 0}}, {(unsigned char*)"eDDot", {226, 169, 183, 0}}, {(unsigned char*)"eDot", {226, 137, 145, 0}}, {(unsigned char*)"eacute", {195, 169, 0}}, {(unsigned char*)"easter", {226, 169, 174, 0}}, {(unsigned char*)"ecaron", {196, 155, 0}}, {(unsigned char*)"ecir", {226, 137, 150, 0}}, {(unsigned char*)"ecirc", {195, 170, 0}}, {(unsigned char*)"ecolon", {226, 137, 149, 0}}, {(unsigned char*)"ecy", {209, 141, 0}}, {(unsigned char*)"edot", {196, 151, 0}}, {(unsigned char*)"ee", {226, 133, 135, 0}}, {(unsigned char*)"efDot", {226, 137, 146, 0}}, {(unsigned char*)"efr", {240, 157, 148, 162, 0}}, {(unsigned char*)"eg", {226, 170, 154, 0}}, {(unsigned char*)"egrave", {195, 168, 0}}, {(unsigned char*)"egs", {226, 170, 150, 0}}, {(unsigned char*)"egsdot", {226, 170, 152, 0}}, {(unsigned char*)"el", {226, 170, 153, 0}}, {(unsigned char*)"elinters", {226, 143, 167, 0}}, {(unsigned char*)"ell", {226, 132, 147, 0}}, {(unsigned char*)"els", {226, 170, 149, 0}}, {(unsigned char*)"elsdot", {226, 170, 151, 0}}, {(unsigned char*)"emacr", {196, 147, 0}}, {(unsigned char*)"empty", {226, 136, 133, 0}}, {(unsigned char*)"emptyset", {226, 136, 133, 0}}, {(unsigned char*)"emptyv", {226, 136, 133, 0}}, {(unsigned char*)"emsp", {226, 128, 131, 0}}, {(unsigned char*)"emsp13", {226, 128, 132, 0}}, {(unsigned char*)"emsp14", {226, 128, 133, 0}}, {(unsigned char*)"eng", {197, 139, 0}}, {(unsigned char*)"ensp", {226, 128, 130, 0}}, {(unsigned char*)"eogon", {196, 153, 0}}, {(unsigned char*)"eopf", {240, 157, 149, 150, 0}}, {(unsigned char*)"epar", {226, 139, 149, 0}}, {(unsigned char*)"eparsl", {226, 167, 163, 0}}, {(unsigned char*)"eplus", {226, 169, 177, 0}}, {(unsigned char*)"epsi", {206, 181, 0}}, {(unsigned char*)"epsilon", {206, 181, 0}}, {(unsigned char*)"epsiv", {207, 181, 0}}, {(unsigned char*)"eqcirc", {226, 137, 150, 0}}, {(unsigned char*)"eqcolon", {226, 137, 149, 0}}, {(unsigned char*)"eqsim", {226, 137, 130, 0}}, {(unsigned char*)"eqslantgtr", {226, 170, 150, 0}}, {(unsigned char*)"eqslantless", {226, 170, 149, 0}}, {(unsigned char*)"equals", {61, 0}}, {(unsigned char*)"equest", {226, 137, 159, 0}}, {(unsigned char*)"equiv", {226, 137, 161, 0}}, {(unsigned char*)"equivDD", {226, 169, 184, 0}}, {(unsigned char*)"eqvparsl", {226, 167, 165, 0}}, {(unsigned char*)"erDot", {226, 137, 147, 0}}, {(unsigned char*)"erarr", {226, 165, 177, 0}}, {(unsigned char*)"escr", {226, 132, 175, 0}}, {(unsigned char*)"esdot", {226, 137, 144, 0}}, {(unsigned char*)"esim", {226, 137, 130, 0}}, {(unsigned char*)"eta", {206, 183, 0}}, {(unsigned char*)"eth", {195, 176, 0}}, {(unsigned char*)"euml", {195, 171, 0}}, {(unsigned char*)"euro", {226, 130, 172, 0}}, {(unsigned char*)"excl", {33, 0}}, {(unsigned char*)"exist", {226, 136, 131, 0}}, {(unsigned char*)"expectation", {226, 132, 176, 0}}, {(unsigned char*)"exponentiale", {226, 133, 135, 0}}, {(unsigned char*)"fallingdotseq", {226, 137, 146, 0}}, {(unsigned char*)"fcy", {209, 132, 0}}, {(unsigned char*)"female", {226, 153, 128, 0}}, {(unsigned char*)"ffilig", {239, 172, 131, 0}}, {(unsigned char*)"fflig", {239, 172, 128, 0}}, {(unsigned char*)"ffllig", {239, 172, 132, 0}}, {(unsigned char*)"ffr", {240, 157, 148, 163, 0}}, {(unsigned char*)"filig", {239, 172, 129, 0}}, {(unsigned char*)"fjlig", {102, 106, 0}}, {(unsigned char*)"flat", {226, 153, 173, 0}}, {(unsigned char*)"fllig", {239, 172, 130, 0}}, {(unsigned char*)"fltns", {226, 150, 177, 0}}, {(unsigned char*)"fnof", {198, 146, 0}}, {(unsigned char*)"fopf", {240, 157, 149, 151, 0}}, {(unsigned char*)"forall", {226, 136, 128, 0}}, {(unsigned char*)"fork", {226, 139, 148, 0}}, {(unsigned char*)"forkv", {226, 171, 153, 0}}, {(unsigned char*)"fpartint", {226, 168, 141, 0}}, {(unsigned char*)"frac12", {194, 189, 0}}, {(unsigned char*)"frac13", {226, 133, 147, 0}}, {(unsigned char*)"frac14", {194, 188, 0}}, {(unsigned char*)"frac15", {226, 133, 149, 0}}, {(unsigned char*)"frac16", {226, 133, 153, 0}}, {(unsigned char*)"frac18", {226, 133, 155, 0}}, {(unsigned char*)"frac23", {226, 133, 148, 0}}, {(unsigned char*)"frac25", {226, 133, 150, 0}}, {(unsigned char*)"frac34", {194, 190, 0}}, {(unsigned char*)"frac35", {226, 133, 151, 0}}, {(unsigned char*)"frac38", {226, 133, 156, 0}}, {(unsigned char*)"frac45", {226, 133, 152, 0}}, {(unsigned char*)"frac56", {226, 133, 154, 0}}, {(unsigned char*)"frac58", {226, 133, 157, 0}}, {(unsigned char*)"frac78", {226, 133, 158, 0}}, {(unsigned char*)"frasl", {226, 129, 132, 0}}, {(unsigned char*)"frown", {226, 140, 162, 0}}, {(unsigned char*)"fscr", {240, 157, 146, 187, 0}}, {(unsigned char*)"gE", {226, 137, 167, 0}}, {(unsigned char*)"gEl", {226, 170, 140, 0}}, {(unsigned char*)"gacute", {199, 181, 0}}, {(unsigned char*)"gamma", {206, 179, 0}}, {(unsigned char*)"gammad", {207, 157, 0}}, {(unsigned char*)"gap", {226, 170, 134, 0}}, {(unsigned char*)"gbreve", {196, 159, 0}}, {(unsigned char*)"gcirc", {196, 157, 0}}, {(unsigned char*)"gcy", {208, 179, 0}}, {(unsigned char*)"gdot", {196, 161, 0}}, {(unsigned char*)"ge", {226, 137, 165, 0}}, {(unsigned char*)"gel", {226, 139, 155, 0}}, {(unsigned char*)"geq", {226, 137, 165, 0}}, {(unsigned char*)"geqq", {226, 137, 167, 0}}, {(unsigned char*)"geqslant", {226, 169, 190, 0}}, {(unsigned char*)"ges", {226, 169, 190, 0}}, {(unsigned char*)"gescc", {226, 170, 169, 0}}, {(unsigned char*)"gesdot", {226, 170, 128, 0}}, {(unsigned char*)"gesdoto", {226, 170, 130, 0}}, {(unsigned char*)"gesdotol", {226, 170, 132, 0}}, {(unsigned char*)"gesl", {226, 139, 155, 239, 184, 128, 0}}, {(unsigned char*)"gesles", {226, 170, 148, 0}}, {(unsigned char*)"gfr", {240, 157, 148, 164, 0}}, {(unsigned char*)"gg", {226, 137, 171, 0}}, {(unsigned char*)"ggg", {226, 139, 153, 0}}, {(unsigned char*)"gimel", {226, 132, 183, 0}}, {(unsigned char*)"gjcy", {209, 147, 0}}, {(unsigned char*)"gl", {226, 137, 183, 0}}, {(unsigned char*)"glE", {226, 170, 146, 0}}, {(unsigned char*)"gla", {226, 170, 165, 0}}, {(unsigned char*)"glj", {226, 170, 164, 0}}, {(unsigned char*)"gnE", {226, 137, 169, 0}}, {(unsigned char*)"gnap", {226, 170, 138, 0}}, {(unsigned char*)"gnapprox", {226, 170, 138, 0}}, {(unsigned char*)"gne", {226, 170, 136, 0}}, {(unsigned char*)"gneq", {226, 170, 136, 0}}, {(unsigned char*)"gneqq", {226, 137, 169, 0}}, {(unsigned char*)"gnsim", {226, 139, 167, 0}}, {(unsigned char*)"gopf", {240, 157, 149, 152, 0}}, {(unsigned char*)"grave", {96, 0}}, {(unsigned char*)"gscr", {226, 132, 138, 0}}, {(unsigned char*)"gsim", {226, 137, 179, 0}}, {(unsigned char*)"gsime", {226, 170, 142, 0}}, {(unsigned char*)"gsiml", {226, 170, 144, 0}}, {(unsigned char*)"gt", {62, 0}}, {(unsigned char*)"gtcc", {226, 170, 167, 0}}, {(unsigned char*)"gtcir", {226, 169, 186, 0}}, {(unsigned char*)"gtdot", {226, 139, 151, 0}}, {(unsigned char*)"gtlPar", {226, 166, 149, 0}}, {(unsigned char*)"gtquest", {226, 169, 188, 0}}, {(unsigned char*)"gtrapprox", {226, 170, 134, 0}}, {(unsigned char*)"gtrarr", {226, 165, 184, 0}}, {(unsigned char*)"gtrdot", {226, 139, 151, 0}}, {(unsigned char*)"gtreqless", {226, 139, 155, 0}}, {(unsigned char*)"gtreqqless", {226, 170, 140, 0}}, {(unsigned char*)"gtrless", {226, 137, 183, 0}}, {(unsigned char*)"gtrsim", {226, 137, 179, 0}}, {(unsigned char*)"gvertneqq", {226, 137, 169, 239, 184, 128, 0}}, {(unsigned char*)"gvnE", {226, 137, 169, 239, 184, 128, 0}}, {(unsigned char*)"hArr", {226, 135, 148, 0}}, {(unsigned char*)"hairsp", {226, 128, 138, 0}}, {(unsigned char*)"half", {194, 189, 0}}, {(unsigned char*)"hamilt", {226, 132, 139, 0}}, {(unsigned char*)"hardcy", {209, 138, 0}}, {(unsigned char*)"harr", {226, 134, 148, 0}}, {(unsigned char*)"harrcir", {226, 165, 136, 0}}, {(unsigned char*)"harrw", {226, 134, 173, 0}}, {(unsigned char*)"hbar", {226, 132, 143, 0}}, {(unsigned char*)"hcirc", {196, 165, 0}}, {(unsigned char*)"hearts", {226, 153, 165, 0}}, {(unsigned char*)"heartsuit", {226, 153, 165, 0}}, {(unsigned char*)"hellip", {226, 128, 166, 0}}, {(unsigned char*)"hercon", {226, 138, 185, 0}}, {(unsigned char*)"hfr", {240, 157, 148, 165, 0}}, {(unsigned char*)"hksearow", {226, 164, 165, 0}}, {(unsigned char*)"hkswarow", {226, 164, 166, 0}}, {(unsigned char*)"hoarr", {226, 135, 191, 0}}, {(unsigned char*)"homtht", {226, 136, 187, 0}}, {(unsigned char*)"hookleftarrow", {226, 134, 169, 0}}, {(unsigned char*)"hookrightarrow", {226, 134, 170, 0}}, {(unsigned char*)"hopf", {240, 157, 149, 153, 0}}, {(unsigned char*)"horbar", {226, 128, 149, 0}}, {(unsigned char*)"hscr", {240, 157, 146, 189, 0}}, {(unsigned char*)"hslash", {226, 132, 143, 0}}, {(unsigned char*)"hstrok", {196, 167, 0}}, {(unsigned char*)"hybull", {226, 129, 131, 0}}, {(unsigned char*)"hyphen", {226, 128, 144, 0}}, {(unsigned char*)"iacute", {195, 173, 0}}, {(unsigned char*)"ic", {226, 129, 163, 0}}, {(unsigned char*)"icirc", {195, 174, 0}}, {(unsigned char*)"icy", {208, 184, 0}}, {(unsigned char*)"iecy", {208, 181, 0}}, {(unsigned char*)"iexcl", {194, 161, 0}}, {(unsigned char*)"iff", {226, 135, 148, 0}}, {(unsigned char*)"ifr", {240, 157, 148, 166, 0}}, {(unsigned char*)"igrave", {195, 172, 0}}, {(unsigned char*)"ii", {226, 133, 136, 0}}, {(unsigned char*)"iiiint", {226, 168, 140, 0}}, {(unsigned char*)"iiint", {226, 136, 173, 0}}, {(unsigned char*)"iinfin", {226, 167, 156, 0}}, {(unsigned char*)"iiota", {226, 132, 169, 0}}, {(unsigned char*)"ijlig", {196, 179, 0}}, {(unsigned char*)"imacr", {196, 171, 0}}, {(unsigned char*)"image", {226, 132, 145, 0}}, {(unsigned char*)"imagline", {226, 132, 144, 0}}, {(unsigned char*)"imagpart", {226, 132, 145, 0}}, {(unsigned char*)"imath", {196, 177, 0}}, {(unsigned char*)"imof", {226, 138, 183, 0}}, {(unsigned char*)"imped", {198, 181, 0}}, {(unsigned char*)"in", {226, 136, 136, 0}}, {(unsigned char*)"incare", {226, 132, 133, 0}}, {(unsigned char*)"infin", {226, 136, 158, 0}}, {(unsigned char*)"infintie", {226, 167, 157, 0}}, {(unsigned char*)"inodot", {196, 177, 0}}, {(unsigned char*)"int", {226, 136, 171, 0}}, {(unsigned char*)"intcal", {226, 138, 186, 0}}, {(unsigned char*)"integers", {226, 132, 164, 0}}, {(unsigned char*)"intercal", {226, 138, 186, 0}}, {(unsigned char*)"intlarhk", {226, 168, 151, 0}}, {(unsigned char*)"intprod", {226, 168, 188, 0}}, {(unsigned char*)"iocy", {209, 145, 0}}, {(unsigned char*)"iogon", {196, 175, 0}}, {(unsigned char*)"iopf", {240, 157, 149, 154, 0}}, {(unsigned char*)"iota", {206, 185, 0}}, {(unsigned char*)"iprod", {226, 168, 188, 0}}, {(unsigned char*)"iquest", {194, 191, 0}}, {(unsigned char*)"iscr", {240, 157, 146, 190, 0}}, {(unsigned char*)"isin", {226, 136, 136, 0}}, {(unsigned char*)"isinE", {226, 139, 185, 0}}, {(unsigned char*)"isindot", {226, 139, 181, 0}}, {(unsigned char*)"isins", {226, 139, 180, 0}}, {(unsigned char*)"isinsv", {226, 139, 179, 0}}, {(unsigned char*)"isinv", {226, 136, 136, 0}}, {(unsigned char*)"it", {226, 129, 162, 0}}, {(unsigned char*)"itilde", {196, 169, 0}}, {(unsigned char*)"iukcy", {209, 150, 0}}, {(unsigned char*)"iuml", {195, 175, 0}}, {(unsigned char*)"jcirc", {196, 181, 0}}, {(unsigned char*)"jcy", {208, 185, 0}}, {(unsigned char*)"jfr", {240, 157, 148, 167, 0}}, {(unsigned char*)"jmath", {200, 183, 0}}, {(unsigned char*)"jopf", {240, 157, 149, 155, 0}}, {(unsigned char*)"jscr", {240, 157, 146, 191, 0}}, {(unsigned char*)"jsercy", {209, 152, 0}}, {(unsigned char*)"jukcy", {209, 148, 0}}, {(unsigned char*)"kappa", {206, 186, 0}}, {(unsigned char*)"kappav", {207, 176, 0}}, {(unsigned char*)"kcedil", {196, 183, 0}}, {(unsigned char*)"kcy", {208, 186, 0}}, {(unsigned char*)"kfr", {240, 157, 148, 168, 0}}, {(unsigned char*)"kgreen", {196, 184, 0}}, {(unsigned char*)"khcy", {209, 133, 0}}, {(unsigned char*)"kjcy", {209, 156, 0}}, {(unsigned char*)"kopf", {240, 157, 149, 156, 0}}, {(unsigned char*)"kscr", {240, 157, 147, 128, 0}}, {(unsigned char*)"lAarr", {226, 135, 154, 0}}, {(unsigned char*)"lArr", {226, 135, 144, 0}}, {(unsigned char*)"lAtail", {226, 164, 155, 0}}, {(unsigned char*)"lBarr", {226, 164, 142, 0}}, {(unsigned char*)"lE", {226, 137, 166, 0}}, {(unsigned char*)"lEg", {226, 170, 139, 0}}, {(unsigned char*)"lHar", {226, 165, 162, 0}}, {(unsigned char*)"lacute", {196, 186, 0}}, {(unsigned char*)"laemptyv", {226, 166, 180, 0}}, {(unsigned char*)"lagran", {226, 132, 146, 0}}, {(unsigned char*)"lambda", {206, 187, 0}}, {(unsigned char*)"lang", {226, 159, 168, 0}}, {(unsigned char*)"langd", {226, 166, 145, 0}}, {(unsigned char*)"langle", {226, 159, 168, 0}}, {(unsigned char*)"lap", {226, 170, 133, 0}}, {(unsigned char*)"laquo", {194, 171, 0}}, {(unsigned char*)"larr", {226, 134, 144, 0}}, {(unsigned char*)"larrb", {226, 135, 164, 0}}, {(unsigned char*)"larrbfs", {226, 164, 159, 0}}, {(unsigned char*)"larrfs", {226, 164, 157, 0}}, {(unsigned char*)"larrhk", {226, 134, 169, 0}}, {(unsigned char*)"larrlp", {226, 134, 171, 0}}, {(unsigned char*)"larrpl", {226, 164, 185, 0}}, {(unsigned char*)"larrsim", {226, 165, 179, 0}}, {(unsigned char*)"larrtl", {226, 134, 162, 0}}, {(unsigned char*)"lat", {226, 170, 171, 0}}, {(unsigned char*)"latail", {226, 164, 153, 0}}, {(unsigned char*)"late", {226, 170, 173, 0}}, {(unsigned char*)"lates", {226, 170, 173, 239, 184, 128, 0}}, {(unsigned char*)"lbarr", {226, 164, 140, 0}}, {(unsigned char*)"lbbrk", {226, 157, 178, 0}}, {(unsigned char*)"lbrace", {123, 0}}, {(unsigned char*)"lbrack", {91, 0}}, {(unsigned char*)"lbrke", {226, 166, 139, 0}}, {(unsigned char*)"lbrksld", {226, 166, 143, 0}}, {(unsigned char*)"lbrkslu", {226, 166, 141, 0}}, {(unsigned char*)"lcaron", {196, 190, 0}}, {(unsigned char*)"lcedil", {196, 188, 0}}, {(unsigned char*)"lceil", {226, 140, 136, 0}}, {(unsigned char*)"lcub", {123, 0}}, {(unsigned char*)"lcy", {208, 187, 0}}, {(unsigned char*)"ldca", {226, 164, 182, 0}}, {(unsigned char*)"ldquo", {226, 128, 156, 0}}, {(unsigned char*)"ldquor", {226, 128, 158, 0}}, {(unsigned char*)"ldrdhar", {226, 165, 167, 0}}, {(unsigned char*)"ldrushar", {226, 165, 139, 0}}, {(unsigned char*)"ldsh", {226, 134, 178, 0}}, {(unsigned char*)"le", {226, 137, 164, 0}}, {(unsigned char*)"leftarrow", {226, 134, 144, 0}}, {(unsigned char*)"leftarrowtail", {226, 134, 162, 0}}, {(unsigned char*)"leftharpoondown", {226, 134, 189, 0}}, {(unsigned char*)"leftharpoonup", {226, 134, 188, 0}}, {(unsigned char*)"leftleftarrows", {226, 135, 135, 0}}, {(unsigned char*)"leftrightarrow", {226, 134, 148, 0}}, {(unsigned char*)"leftrightarrows", {226, 135, 134, 0}}, {(unsigned char*)"leftrightharpoons", {226, 135, 139, 0}}, {(unsigned char*)"leftrightsquigarrow", {226, 134, 173, 0}}, {(unsigned char*)"leftthreetimes", {226, 139, 139, 0}}, {(unsigned char*)"leg", {226, 139, 154, 0}}, {(unsigned char*)"leq", {226, 137, 164, 0}}, {(unsigned char*)"leqq", {226, 137, 166, 0}}, {(unsigned char*)"leqslant", {226, 169, 189, 0}}, {(unsigned char*)"les", {226, 169, 189, 0}}, {(unsigned char*)"lescc", {226, 170, 168, 0}}, {(unsigned char*)"lesdot", {226, 169, 191, 0}}, {(unsigned char*)"lesdoto", {226, 170, 129, 0}}, {(unsigned char*)"lesdotor", {226, 170, 131, 0}}, {(unsigned char*)"lesg", {226, 139, 154, 239, 184, 128, 0}}, {(unsigned char*)"lesges", {226, 170, 147, 0}}, {(unsigned char*)"lessapprox", {226, 170, 133, 0}}, {(unsigned char*)"lessdot", {226, 139, 150, 0}}, {(unsigned char*)"lesseqgtr", {226, 139, 154, 0}}, {(unsigned char*)"lesseqqgtr", {226, 170, 139, 0}}, {(unsigned char*)"lessgtr", {226, 137, 182, 0}}, {(unsigned char*)"lesssim", {226, 137, 178, 0}}, {(unsigned char*)"lfisht", {226, 165, 188, 0}}, {(unsigned char*)"lfloor", {226, 140, 138, 0}}, {(unsigned char*)"lfr", {240, 157, 148, 169, 0}}, {(unsigned char*)"lg", {226, 137, 182, 0}}, {(unsigned char*)"lgE", {226, 170, 145, 0}}, {(unsigned char*)"lhard", {226, 134, 189, 0}}, {(unsigned char*)"lharu", {226, 134, 188, 0}}, {(unsigned char*)"lharul", {226, 165, 170, 0}}, {(unsigned char*)"lhblk", {226, 150, 132, 0}}, {(unsigned char*)"ljcy", {209, 153, 0}}, {(unsigned char*)"ll", {226, 137, 170, 0}}, {(unsigned char*)"llarr", {226, 135, 135, 0}}, {(unsigned char*)"llcorner", {226, 140, 158, 0}}, {(unsigned char*)"llhard", {226, 165, 171, 0}}, {(unsigned char*)"lltri", {226, 151, 186, 0}}, {(unsigned char*)"lmidot", {197, 128, 0}}, {(unsigned char*)"lmoust", {226, 142, 176, 0}}, {(unsigned char*)"lmoustache", {226, 142, 176, 0}}, {(unsigned char*)"lnE", {226, 137, 168, 0}}, {(unsigned char*)"lnap", {226, 170, 137, 0}}, {(unsigned char*)"lnapprox", {226, 170, 137, 0}}, {(unsigned char*)"lne", {226, 170, 135, 0}}, {(unsigned char*)"lneq", {226, 170, 135, 0}}, {(unsigned char*)"lneqq", {226, 137, 168, 0}}, {(unsigned char*)"lnsim", {226, 139, 166, 0}}, {(unsigned char*)"loang", {226, 159, 172, 0}}, {(unsigned char*)"loarr", {226, 135, 189, 0}}, {(unsigned char*)"lobrk", {226, 159, 166, 0}}, {(unsigned char*)"longleftarrow", {226, 159, 181, 0}}, {(unsigned char*)"longleftrightarrow", {226, 159, 183, 0}}, {(unsigned char*)"longmapsto", {226, 159, 188, 0}}, {(unsigned char*)"longrightarrow", {226, 159, 182, 0}}, {(unsigned char*)"looparrowleft", {226, 134, 171, 0}}, {(unsigned char*)"looparrowright", {226, 134, 172, 0}}, {(unsigned char*)"lopar", {226, 166, 133, 0}}, {(unsigned char*)"lopf", {240, 157, 149, 157, 0}}, {(unsigned char*)"loplus", {226, 168, 173, 0}}, {(unsigned char*)"lotimes", {226, 168, 180, 0}}, {(unsigned char*)"lowast", {226, 136, 151, 0}}, {(unsigned char*)"lowbar", {95, 0}}, {(unsigned char*)"loz", {226, 151, 138, 0}}, {(unsigned char*)"lozenge", {226, 151, 138, 0}}, {(unsigned char*)"lozf", {226, 167, 171, 0}}, {(unsigned char*)"lpar", {40, 0}}, {(unsigned char*)"lparlt", {226, 166, 147, 0}}, {(unsigned char*)"lrarr", {226, 135, 134, 0}}, {(unsigned char*)"lrcorner", {226, 140, 159, 0}}, {(unsigned char*)"lrhar", {226, 135, 139, 0}}, {(unsigned char*)"lrhard", {226, 165, 173, 0}}, {(unsigned char*)"lrm", {226, 128, 142, 0}}, {(unsigned char*)"lrtri", {226, 138, 191, 0}}, {(unsigned char*)"lsaquo", {226, 128, 185, 0}}, {(unsigned char*)"lscr", {240, 157, 147, 129, 0}}, {(unsigned char*)"lsh", {226, 134, 176, 0}}, {(unsigned char*)"lsim", {226, 137, 178, 0}}, {(unsigned char*)"lsime", {226, 170, 141, 0}}, {(unsigned char*)"lsimg", {226, 170, 143, 0}}, {(unsigned char*)"lsqb", {91, 0}}, {(unsigned char*)"lsquo", {226, 128, 152, 0}}, {(unsigned char*)"lsquor", {226, 128, 154, 0}}, {(unsigned char*)"lstrok", {197, 130, 0}}, {(unsigned char*)"lt", {60, 0}}, {(unsigned char*)"ltcc", {226, 170, 166, 0}}, {(unsigned char*)"ltcir", {226, 169, 185, 0}}, {(unsigned char*)"ltdot", {226, 139, 150, 0}}, {(unsigned char*)"lthree", {226, 139, 139, 0}}, {(unsigned char*)"ltimes", {226, 139, 137, 0}}, {(unsigned char*)"ltlarr", {226, 165, 182, 0}}, {(unsigned char*)"ltquest", {226, 169, 187, 0}}, {(unsigned char*)"ltrPar", {226, 166, 150, 0}}, {(unsigned char*)"ltri", {226, 151, 131, 0}}, {(unsigned char*)"ltrie", {226, 138, 180, 0}}, {(unsigned char*)"ltrif", {226, 151, 130, 0}}, {(unsigned char*)"lurdshar", {226, 165, 138, 0}}, {(unsigned char*)"luruhar", {226, 165, 166, 0}}, {(unsigned char*)"lvertneqq", {226, 137, 168, 239, 184, 128, 0}}, {(unsigned char*)"lvnE", {226, 137, 168, 239, 184, 128, 0}}, {(unsigned char*)"mDDot", {226, 136, 186, 0}}, {(unsigned char*)"macr", {194, 175, 0}}, {(unsigned char*)"male", {226, 153, 130, 0}}, {(unsigned char*)"malt", {226, 156, 160, 0}}, {(unsigned char*)"maltese", {226, 156, 160, 0}}, {(unsigned char*)"map", {226, 134, 166, 0}}, {(unsigned char*)"mapsto", {226, 134, 166, 0}}, {(unsigned char*)"mapstodown", {226, 134, 167, 0}}, {(unsigned char*)"mapstoleft", {226, 134, 164, 0}}, {(unsigned char*)"mapstoup", {226, 134, 165, 0}}, {(unsigned char*)"marker", {226, 150, 174, 0}}, {(unsigned char*)"mcomma", {226, 168, 169, 0}}, {(unsigned char*)"mcy", {208, 188, 0}}, {(unsigned char*)"mdash", {226, 128, 148, 0}}, {(unsigned char*)"measuredangle", {226, 136, 161, 0}}, {(unsigned char*)"mfr", {240, 157, 148, 170, 0}}, {(unsigned char*)"mho", {226, 132, 167, 0}}, {(unsigned char*)"micro", {194, 181, 0}}, {(unsigned char*)"mid", {226, 136, 163, 0}}, {(unsigned char*)"midast", {42, 0}}, {(unsigned char*)"midcir", {226, 171, 176, 0}}, {(unsigned char*)"middot", {194, 183, 0}}, {(unsigned char*)"minus", {226, 136, 146, 0}}, {(unsigned char*)"minusb", {226, 138, 159, 0}}, {(unsigned char*)"minusd", {226, 136, 184, 0}}, {(unsigned char*)"minusdu", {226, 168, 170, 0}}, {(unsigned char*)"mlcp", {226, 171, 155, 0}}, {(unsigned char*)"mldr", {226, 128, 166, 0}}, {(unsigned char*)"mnplus", {226, 136, 147, 0}}, {(unsigned char*)"models", {226, 138, 167, 0}}, {(unsigned char*)"mopf", {240, 157, 149, 158, 0}}, {(unsigned char*)"mp", {226, 136, 147, 0}}, {(unsigned char*)"mscr", {240, 157, 147, 130, 0}}, {(unsigned char*)"mstpos", {226, 136, 190, 0}}, {(unsigned char*)"mu", {206, 188, 0}}, {(unsigned char*)"multimap", {226, 138, 184, 0}}, {(unsigned char*)"mumap", {226, 138, 184, 0}}, {(unsigned char*)"nGg", {226, 139, 153, 204, 184, 0}}, {(unsigned char*)"nGt", {226, 137, 171, 226, 131, 146, 0}}, {(unsigned char*)"nGtv", {226, 137, 171, 204, 184, 0}}, {(unsigned char*)"nLeftarrow", {226, 135, 141, 0}}, {(unsigned char*)"nLeftrightarrow", {226, 135, 142, 0}}, {(unsigned char*)"nLl", {226, 139, 152, 204, 184, 0}}, {(unsigned char*)"nLt", {226, 137, 170, 226, 131, 146, 0}}, {(unsigned char*)"nLtv", {226, 137, 170, 204, 184, 0}}, {(unsigned char*)"nRightarrow", {226, 135, 143, 0}}, {(unsigned char*)"nVDash", {226, 138, 175, 0}}, {(unsigned char*)"nVdash", {226, 138, 174, 0}}, {(unsigned char*)"nabla", {226, 136, 135, 0}}, {(unsigned char*)"nacute", {197, 132, 0}}, {(unsigned char*)"nang", {226, 136, 160, 226, 131, 146, 0}}, {(unsigned char*)"nap", {226, 137, 137, 0}}, {(unsigned char*)"napE", {226, 169, 176, 204, 184, 0}}, {(unsigned char*)"napid", {226, 137, 139, 204, 184, 0}}, {(unsigned char*)"napos", {197, 137, 0}}, {(unsigned char*)"napprox", {226, 137, 137, 0}}, {(unsigned char*)"natur", {226, 153, 174, 0}}, {(unsigned char*)"natural", {226, 153, 174, 0}}, {(unsigned char*)"naturals", {226, 132, 149, 0}}, {(unsigned char*)"nbsp", {194, 160, 0}}, {(unsigned char*)"nbump", {226, 137, 142, 204, 184, 0}}, {(unsigned char*)"nbumpe", {226, 137, 143, 204, 184, 0}}, {(unsigned char*)"ncap", {226, 169, 131, 0}}, {(unsigned char*)"ncaron", {197, 136, 0}}, {(unsigned char*)"ncedil", {197, 134, 0}}, {(unsigned char*)"ncong", {226, 137, 135, 0}}, {(unsigned char*)"ncongdot", {226, 169, 173, 204, 184, 0}}, {(unsigned char*)"ncup", {226, 169, 130, 0}}, {(unsigned char*)"ncy", {208, 189, 0}}, {(unsigned char*)"ndash", {226, 128, 147, 0}}, {(unsigned char*)"ne", {226, 137, 160, 0}}, {(unsigned char*)"neArr", {226, 135, 151, 0}}, {(unsigned char*)"nearhk", {226, 164, 164, 0}}, {(unsigned char*)"nearr", {226, 134, 151, 0}}, {(unsigned char*)"nearrow", {226, 134, 151, 0}}, {(unsigned char*)"nedot", {226, 137, 144, 204, 184, 0}}, {(unsigned char*)"nequiv", {226, 137, 162, 0}}, {(unsigned char*)"nesear", {226, 164, 168, 0}}, {(unsigned char*)"nesim", {226, 137, 130, 204, 184, 0}}, {(unsigned char*)"nexist", {226, 136, 132, 0}}, {(unsigned char*)"nexists", {226, 136, 132, 0}}, {(unsigned char*)"nfr", {240, 157, 148, 171, 0}}, {(unsigned char*)"ngE", {226, 137, 167, 204, 184, 0}}, {(unsigned char*)"nge", {226, 137, 177, 0}}, {(unsigned char*)"ngeq", {226, 137, 177, 0}}, {(unsigned char*)"ngeqq", {226, 137, 167, 204, 184, 0}}, {(unsigned char*)"ngeqslant", {226, 169, 190, 204, 184, 0}}, {(unsigned char*)"nges", {226, 169, 190, 204, 184, 0}}, {(unsigned char*)"ngsim", {226, 137, 181, 0}}, {(unsigned char*)"ngt", {226, 137, 175, 0}}, {(unsigned char*)"ngtr", {226, 137, 175, 0}}, {(unsigned char*)"nhArr", {226, 135, 142, 0}}, {(unsigned char*)"nharr", {226, 134, 174, 0}}, {(unsigned char*)"nhpar", {226, 171, 178, 0}}, {(unsigned char*)"ni", {226, 136, 139, 0}}, {(unsigned char*)"nis", {226, 139, 188, 0}}, {(unsigned char*)"nisd", {226, 139, 186, 0}}, {(unsigned char*)"niv", {226, 136, 139, 0}}, {(unsigned char*)"njcy", {209, 154, 0}}, {(unsigned char*)"nlArr", {226, 135, 141, 0}}, {(unsigned char*)"nlE", {226, 137, 166, 204, 184, 0}}, {(unsigned char*)"nlarr", {226, 134, 154, 0}}, {(unsigned char*)"nldr", {226, 128, 165, 0}}, {(unsigned char*)"nle", {226, 137, 176, 0}}, {(unsigned char*)"nleftarrow", {226, 134, 154, 0}}, {(unsigned char*)"nleftrightarrow", {226, 134, 174, 0}}, {(unsigned char*)"nleq", {226, 137, 176, 0}}, {(unsigned char*)"nleqq", {226, 137, 166, 204, 184, 0}}, {(unsigned char*)"nleqslant", {226, 169, 189, 204, 184, 0}}, {(unsigned char*)"nles", {226, 169, 189, 204, 184, 0}}, {(unsigned char*)"nless", {226, 137, 174, 0}}, {(unsigned char*)"nlsim", {226, 137, 180, 0}}, {(unsigned char*)"nlt", {226, 137, 174, 0}}, {(unsigned char*)"nltri", {226, 139, 170, 0}}, {(unsigned char*)"nltrie", {226, 139, 172, 0}}, {(unsigned char*)"nmid", {226, 136, 164, 0}}, {(unsigned char*)"nopf", {240, 157, 149, 159, 0}}, {(unsigned char*)"not", {194, 172, 0}}, {(unsigned char*)"notin", {226, 136, 137, 0}}, {(unsigned char*)"notinE", {226, 139, 185, 204, 184, 0}}, {(unsigned char*)"notindot", {226, 139, 181, 204, 184, 0}}, {(unsigned char*)"notinva", {226, 136, 137, 0}}, {(unsigned char*)"notinvb", {226, 139, 183, 0}}, {(unsigned char*)"notinvc", {226, 139, 182, 0}}, {(unsigned char*)"notni", {226, 136, 140, 0}}, {(unsigned char*)"notniva", {226, 136, 140, 0}}, {(unsigned char*)"notnivb", {226, 139, 190, 0}}, {(unsigned char*)"notnivc", {226, 139, 189, 0}}, {(unsigned char*)"npar", {226, 136, 166, 0}}, {(unsigned char*)"nparallel", {226, 136, 166, 0}}, {(unsigned char*)"nparsl", {226, 171, 189, 226, 131, 165, 0}}, {(unsigned char*)"npart", {226, 136, 130, 204, 184, 0}}, {(unsigned char*)"npolint", {226, 168, 148, 0}}, {(unsigned char*)"npr", {226, 138, 128, 0}}, {(unsigned char*)"nprcue", {226, 139, 160, 0}}, {(unsigned char*)"npre", {226, 170, 175, 204, 184, 0}}, {(unsigned char*)"nprec", {226, 138, 128, 0}}, {(unsigned char*)"npreceq", {226, 170, 175, 204, 184, 0}}, {(unsigned char*)"nrArr", {226, 135, 143, 0}}, {(unsigned char*)"nrarr", {226, 134, 155, 0}}, {(unsigned char*)"nrarrc", {226, 164, 179, 204, 184, 0}}, {(unsigned char*)"nrarrw", {226, 134, 157, 204, 184, 0}}, {(unsigned char*)"nrightarrow", {226, 134, 155, 0}}, {(unsigned char*)"nrtri", {226, 139, 171, 0}}, {(unsigned char*)"nrtrie", {226, 139, 173, 0}}, {(unsigned char*)"nsc", {226, 138, 129, 0}}, {(unsigned char*)"nsccue", {226, 139, 161, 0}}, {(unsigned char*)"nsce", {226, 170, 176, 204, 184, 0}}, {(unsigned char*)"nscr", {240, 157, 147, 131, 0}}, {(unsigned char*)"nshortmid", {226, 136, 164, 0}}, {(unsigned char*)"nshortparallel", {226, 136, 166, 0}}, {(unsigned char*)"nsim", {226, 137, 129, 0}}, {(unsigned char*)"nsime", {226, 137, 132, 0}}, {(unsigned char*)"nsimeq", {226, 137, 132, 0}}, {(unsigned char*)"nsmid", {226, 136, 164, 0}}, {(unsigned char*)"nspar", {226, 136, 166, 0}}, {(unsigned char*)"nsqsube", {226, 139, 162, 0}}, {(unsigned char*)"nsqsupe", {226, 139, 163, 0}}, {(unsigned char*)"nsub", {226, 138, 132, 0}}, {(unsigned char*)"nsubE", {226, 171, 133, 204, 184, 0}}, {(unsigned char*)"nsube", {226, 138, 136, 0}}, {(unsigned char*)"nsubset", {226, 138, 130, 226, 131, 146, 0}}, {(unsigned char*)"nsubseteq", {226, 138, 136, 0}}, {(unsigned char*)"nsubseteqq", {226, 171, 133, 204, 184, 0}}, {(unsigned char*)"nsucc", {226, 138, 129, 0}}, {(unsigned char*)"nsucceq", {226, 170, 176, 204, 184, 0}}, {(unsigned char*)"nsup", {226, 138, 133, 0}}, {(unsigned char*)"nsupE", {226, 171, 134, 204, 184, 0}}, {(unsigned char*)"nsupe", {226, 138, 137, 0}}, {(unsigned char*)"nsupset", {226, 138, 131, 226, 131, 146, 0}}, {(unsigned char*)"nsupseteq", {226, 138, 137, 0}}, {(unsigned char*)"nsupseteqq", {226, 171, 134, 204, 184, 0}}, {(unsigned char*)"ntgl", {226, 137, 185, 0}}, {(unsigned char*)"ntilde", {195, 177, 0}}, {(unsigned char*)"ntlg", {226, 137, 184, 0}}, {(unsigned char*)"ntriangleleft", {226, 139, 170, 0}}, {(unsigned char*)"ntrianglelefteq", {226, 139, 172, 0}}, {(unsigned char*)"ntriangleright", {226, 139, 171, 0}}, {(unsigned char*)"ntrianglerighteq", {226, 139, 173, 0}}, {(unsigned char*)"nu", {206, 189, 0}}, {(unsigned char*)"num", {35, 0}}, {(unsigned char*)"numero", {226, 132, 150, 0}}, {(unsigned char*)"numsp", {226, 128, 135, 0}}, {(unsigned char*)"nvDash", {226, 138, 173, 0}}, {(unsigned char*)"nvHarr", {226, 164, 132, 0}}, {(unsigned char*)"nvap", {226, 137, 141, 226, 131, 146, 0}}, {(unsigned char*)"nvdash", {226, 138, 172, 0}}, {(unsigned char*)"nvge", {226, 137, 165, 226, 131, 146, 0}}, {(unsigned char*)"nvgt", {62, 226, 131, 146, 0}}, {(unsigned char*)"nvinfin", {226, 167, 158, 0}}, {(unsigned char*)"nvlArr", {226, 164, 130, 0}}, {(unsigned char*)"nvle", {226, 137, 164, 226, 131, 146, 0}}, {(unsigned char*)"nvlt", {60, 226, 131, 146, 0}}, {(unsigned char*)"nvltrie", {226, 138, 180, 226, 131, 146, 0}}, {(unsigned char*)"nvrArr", {226, 164, 131, 0}}, {(unsigned char*)"nvrtrie", {226, 138, 181, 226, 131, 146, 0}}, {(unsigned char*)"nvsim", {226, 136, 188, 226, 131, 146, 0}}, {(unsigned char*)"nwArr", {226, 135, 150, 0}}, {(unsigned char*)"nwarhk", {226, 164, 163, 0}}, {(unsigned char*)"nwarr", {226, 134, 150, 0}}, {(unsigned char*)"nwarrow", {226, 134, 150, 0}}, {(unsigned char*)"nwnear", {226, 164, 167, 0}}, {(unsigned char*)"oS", {226, 147, 136, 0}}, {(unsigned char*)"oacute", {195, 179, 0}}, {(unsigned char*)"oast", {226, 138, 155, 0}}, {(unsigned char*)"ocir", {226, 138, 154, 0}}, {(unsigned char*)"ocirc", {195, 180, 0}}, {(unsigned char*)"ocy", {208, 190, 0}}, {(unsigned char*)"odash", {226, 138, 157, 0}}, {(unsigned char*)"odblac", {197, 145, 0}}, {(unsigned char*)"odiv", {226, 168, 184, 0}}, {(unsigned char*)"odot", {226, 138, 153, 0}}, {(unsigned char*)"odsold", {226, 166, 188, 0}}, {(unsigned char*)"oelig", {197, 147, 0}}, {(unsigned char*)"ofcir", {226, 166, 191, 0}}, {(unsigned char*)"ofr", {240, 157, 148, 172, 0}}, {(unsigned char*)"ogon", {203, 155, 0}}, {(unsigned char*)"ograve", {195, 178, 0}}, {(unsigned char*)"ogt", {226, 167, 129, 0}}, {(unsigned char*)"ohbar", {226, 166, 181, 0}}, {(unsigned char*)"ohm", {206, 169, 0}}, {(unsigned char*)"oint", {226, 136, 174, 0}}, {(unsigned char*)"olarr", {226, 134, 186, 0}}, {(unsigned char*)"olcir", {226, 166, 190, 0}}, {(unsigned char*)"olcross", {226, 166, 187, 0}}, {(unsigned char*)"oline", {226, 128, 190, 0}}, {(unsigned char*)"olt", {226, 167, 128, 0}}, {(unsigned char*)"omacr", {197, 141, 0}}, {(unsigned char*)"omega", {207, 137, 0}}, {(unsigned char*)"omicron", {206, 191, 0}}, {(unsigned char*)"omid", {226, 166, 182, 0}}, {(unsigned char*)"ominus", {226, 138, 150, 0}}, {(unsigned char*)"oopf", {240, 157, 149, 160, 0}}, {(unsigned char*)"opar", {226, 166, 183, 0}}, {(unsigned char*)"operp", {226, 166, 185, 0}}, {(unsigned char*)"oplus", {226, 138, 149, 0}}, {(unsigned char*)"or", {226, 136, 168, 0}}, {(unsigned char*)"orarr", {226, 134, 187, 0}}, {(unsigned char*)"ord", {226, 169, 157, 0}}, {(unsigned char*)"order", {226, 132, 180, 0}}, {(unsigned char*)"orderof", {226, 132, 180, 0}}, {(unsigned char*)"ordf", {194, 170, 0}}, {(unsigned char*)"ordm", {194, 186, 0}}, {(unsigned char*)"origof", {226, 138, 182, 0}}, {(unsigned char*)"oror", {226, 169, 150, 0}}, {(unsigned char*)"orslope", {226, 169, 151, 0}}, {(unsigned char*)"orv", {226, 169, 155, 0}}, {(unsigned char*)"oscr", {226, 132, 180, 0}}, {(unsigned char*)"oslash", {195, 184, 0}}, {(unsigned char*)"osol", {226, 138, 152, 0}}, {(unsigned char*)"otilde", {195, 181, 0}}, {(unsigned char*)"otimes", {226, 138, 151, 0}}, {(unsigned char*)"otimesas", {226, 168, 182, 0}}, {(unsigned char*)"ouml", {195, 182, 0}}, {(unsigned char*)"ovbar", {226, 140, 189, 0}}, {(unsigned char*)"par", {226, 136, 165, 0}}, {(unsigned char*)"para", {194, 182, 0}}, {(unsigned char*)"parallel", {226, 136, 165, 0}}, {(unsigned char*)"parsim", {226, 171, 179, 0}}, {(unsigned char*)"parsl", {226, 171, 189, 0}}, {(unsigned char*)"part", {226, 136, 130, 0}}, {(unsigned char*)"pcy", {208, 191, 0}}, {(unsigned char*)"percnt", {37, 0}}, {(unsigned char*)"period", {46, 0}}, {(unsigned char*)"permil", {226, 128, 176, 0}}, {(unsigned char*)"perp", {226, 138, 165, 0}}, {(unsigned char*)"pertenk", {226, 128, 177, 0}}, {(unsigned char*)"pfr", {240, 157, 148, 173, 0}}, {(unsigned char*)"phi", {207, 134, 0}}, {(unsigned char*)"phiv", {207, 149, 0}}, {(unsigned char*)"phmmat", {226, 132, 179, 0}}, {(unsigned char*)"phone", {226, 152, 142, 0}}, {(unsigned char*)"pi", {207, 128, 0}}, {(unsigned char*)"pitchfork", {226, 139, 148, 0}}, {(unsigned char*)"piv", {207, 150, 0}}, {(unsigned char*)"planck", {226, 132, 143, 0}}, {(unsigned char*)"planckh", {226, 132, 142, 0}}, {(unsigned char*)"plankv", {226, 132, 143, 0}}, {(unsigned char*)"plus", {43, 0}}, {(unsigned char*)"plusacir", {226, 168, 163, 0}}, {(unsigned char*)"plusb", {226, 138, 158, 0}}, {(unsigned char*)"pluscir", {226, 168, 162, 0}}, {(unsigned char*)"plusdo", {226, 136, 148, 0}}, {(unsigned char*)"plusdu", {226, 168, 165, 0}}, {(unsigned char*)"pluse", {226, 169, 178, 0}}, {(unsigned char*)"plusmn", {194, 177, 0}}, {(unsigned char*)"plussim", {226, 168, 166, 0}}, {(unsigned char*)"plustwo", {226, 168, 167, 0}}, {(unsigned char*)"pm", {194, 177, 0}}, {(unsigned char*)"pointint", {226, 168, 149, 0}}, {(unsigned char*)"popf", {240, 157, 149, 161, 0}}, {(unsigned char*)"pound", {194, 163, 0}}, {(unsigned char*)"pr", {226, 137, 186, 0}}, {(unsigned char*)"prE", {226, 170, 179, 0}}, {(unsigned char*)"prap", {226, 170, 183, 0}}, {(unsigned char*)"prcue", {226, 137, 188, 0}}, {(unsigned char*)"pre", {226, 170, 175, 0}}, {(unsigned char*)"prec", {226, 137, 186, 0}}, {(unsigned char*)"precapprox", {226, 170, 183, 0}}, {(unsigned char*)"preccurlyeq", {226, 137, 188, 0}}, {(unsigned char*)"preceq", {226, 170, 175, 0}}, {(unsigned char*)"precnapprox", {226, 170, 185, 0}}, {(unsigned char*)"precneqq", {226, 170, 181, 0}}, {(unsigned char*)"precnsim", {226, 139, 168, 0}}, {(unsigned char*)"precsim", {226, 137, 190, 0}}, {(unsigned char*)"prime", {226, 128, 178, 0}}, {(unsigned char*)"primes", {226, 132, 153, 0}}, {(unsigned char*)"prnE", {226, 170, 181, 0}}, {(unsigned char*)"prnap", {226, 170, 185, 0}}, {(unsigned char*)"prnsim", {226, 139, 168, 0}}, {(unsigned char*)"prod", {226, 136, 143, 0}}, {(unsigned char*)"profalar", {226, 140, 174, 0}}, {(unsigned char*)"profline", {226, 140, 146, 0}}, {(unsigned char*)"profsurf", {226, 140, 147, 0}}, {(unsigned char*)"prop", {226, 136, 157, 0}}, {(unsigned char*)"propto", {226, 136, 157, 0}}, {(unsigned char*)"prsim", {226, 137, 190, 0}}, {(unsigned char*)"prurel", {226, 138, 176, 0}}, {(unsigned char*)"pscr", {240, 157, 147, 133, 0}}, {(unsigned char*)"psi", {207, 136, 0}}, {(unsigned char*)"puncsp", {226, 128, 136, 0}}, {(unsigned char*)"qfr", {240, 157, 148, 174, 0}}, {(unsigned char*)"qint", {226, 168, 140, 0}}, {(unsigned char*)"qopf", {240, 157, 149, 162, 0}}, {(unsigned char*)"qprime", {226, 129, 151, 0}}, {(unsigned char*)"qscr", {240, 157, 147, 134, 0}}, {(unsigned char*)"quaternions", {226, 132, 141, 0}}, {(unsigned char*)"quatint", {226, 168, 150, 0}}, {(unsigned char*)"quest", {63, 0}}, {(unsigned char*)"questeq", {226, 137, 159, 0}}, {(unsigned char*)"quot", {34, 0}}, {(unsigned char*)"rAarr", {226, 135, 155, 0}}, {(unsigned char*)"rArr", {226, 135, 146, 0}}, {(unsigned char*)"rAtail", {226, 164, 156, 0}}, {(unsigned char*)"rBarr", {226, 164, 143, 0}}, {(unsigned char*)"rHar", {226, 165, 164, 0}}, {(unsigned char*)"race", {226, 136, 189, 204, 177, 0}}, {(unsigned char*)"racute", {197, 149, 0}}, {(unsigned char*)"radic", {226, 136, 154, 0}}, {(unsigned char*)"raemptyv", {226, 166, 179, 0}}, {(unsigned char*)"rang", {226, 159, 169, 0}}, {(unsigned char*)"rangd", {226, 166, 146, 0}}, {(unsigned char*)"range", {226, 166, 165, 0}}, {(unsigned char*)"rangle", {226, 159, 169, 0}}, {(unsigned char*)"raquo", {194, 187, 0}}, {(unsigned char*)"rarr", {226, 134, 146, 0}}, {(unsigned char*)"rarrap", {226, 165, 181, 0}}, {(unsigned char*)"rarrb", {226, 135, 165, 0}}, {(unsigned char*)"rarrbfs", {226, 164, 160, 0}}, {(unsigned char*)"rarrc", {226, 164, 179, 0}}, {(unsigned char*)"rarrfs", {226, 164, 158, 0}}, {(unsigned char*)"rarrhk", {226, 134, 170, 0}}, {(unsigned char*)"rarrlp", {226, 134, 172, 0}}, {(unsigned char*)"rarrpl", {226, 165, 133, 0}}, {(unsigned char*)"rarrsim", {226, 165, 180, 0}}, {(unsigned char*)"rarrtl", {226, 134, 163, 0}}, {(unsigned char*)"rarrw", {226, 134, 157, 0}}, {(unsigned char*)"ratail", {226, 164, 154, 0}}, {(unsigned char*)"ratio", {226, 136, 182, 0}}, {(unsigned char*)"rationals", {226, 132, 154, 0}}, {(unsigned char*)"rbarr", {226, 164, 141, 0}}, {(unsigned char*)"rbbrk", {226, 157, 179, 0}}, {(unsigned char*)"rbrace", {125, 0}}, {(unsigned char*)"rbrack", {93, 0}}, {(unsigned char*)"rbrke", {226, 166, 140, 0}}, {(unsigned char*)"rbrksld", {226, 166, 142, 0}}, {(unsigned char*)"rbrkslu", {226, 166, 144, 0}}, {(unsigned char*)"rcaron", {197, 153, 0}}, {(unsigned char*)"rcedil", {197, 151, 0}}, {(unsigned char*)"rceil", {226, 140, 137, 0}}, {(unsigned char*)"rcub", {125, 0}}, {(unsigned char*)"rcy", {209, 128, 0}}, {(unsigned char*)"rdca", {226, 164, 183, 0}}, {(unsigned char*)"rdldhar", {226, 165, 169, 0}}, {(unsigned char*)"rdquo", {226, 128, 157, 0}}, {(unsigned char*)"rdquor", {226, 128, 157, 0}}, {(unsigned char*)"rdsh", {226, 134, 179, 0}}, {(unsigned char*)"real", {226, 132, 156, 0}}, {(unsigned char*)"realine", {226, 132, 155, 0}}, {(unsigned char*)"realpart", {226, 132, 156, 0}}, {(unsigned char*)"reals", {226, 132, 157, 0}}, {(unsigned char*)"rect", {226, 150, 173, 0}}, {(unsigned char*)"reg", {194, 174, 0}}, {(unsigned char*)"rfisht", {226, 165, 189, 0}}, {(unsigned char*)"rfloor", {226, 140, 139, 0}}, {(unsigned char*)"rfr", {240, 157, 148, 175, 0}}, {(unsigned char*)"rhard", {226, 135, 129, 0}}, {(unsigned char*)"rharu", {226, 135, 128, 0}}, {(unsigned char*)"rharul", {226, 165, 172, 0}}, {(unsigned char*)"rho", {207, 129, 0}}, {(unsigned char*)"rhov", {207, 177, 0}}, {(unsigned char*)"rightarrow", {226, 134, 146, 0}}, {(unsigned char*)"rightarrowtail", {226, 134, 163, 0}}, {(unsigned char*)"rightharpoondown", {226, 135, 129, 0}}, {(unsigned char*)"rightharpoonup", {226, 135, 128, 0}}, {(unsigned char*)"rightleftarrows", {226, 135, 132, 0}}, {(unsigned char*)"rightleftharpoons", {226, 135, 140, 0}}, {(unsigned char*)"rightrightarrows", {226, 135, 137, 0}}, {(unsigned char*)"rightsquigarrow", {226, 134, 157, 0}}, {(unsigned char*)"rightthreetimes", {226, 139, 140, 0}}, {(unsigned char*)"ring", {203, 154, 0}}, {(unsigned char*)"risingdotseq", {226, 137, 147, 0}}, {(unsigned char*)"rlarr", {226, 135, 132, 0}}, {(unsigned char*)"rlhar", {226, 135, 140, 0}}, {(unsigned char*)"rlm", {226, 128, 143, 0}}, {(unsigned char*)"rmoust", {226, 142, 177, 0}}, {(unsigned char*)"rmoustache", {226, 142, 177, 0}}, {(unsigned char*)"rnmid", {226, 171, 174, 0}}, {(unsigned char*)"roang", {226, 159, 173, 0}}, {(unsigned char*)"roarr", {226, 135, 190, 0}}, {(unsigned char*)"robrk", {226, 159, 167, 0}}, {(unsigned char*)"ropar", {226, 166, 134, 0}}, {(unsigned char*)"ropf", {240, 157, 149, 163, 0}}, {(unsigned char*)"roplus", {226, 168, 174, 0}}, {(unsigned char*)"rotimes", {226, 168, 181, 0}}, {(unsigned char*)"rpar", {41, 0}}, {(unsigned char*)"rpargt", {226, 166, 148, 0}}, {(unsigned char*)"rppolint", {226, 168, 146, 0}}, {(unsigned char*)"rrarr", {226, 135, 137, 0}}, {(unsigned char*)"rsaquo", {226, 128, 186, 0}}, {(unsigned char*)"rscr", {240, 157, 147, 135, 0}}, {(unsigned char*)"rsh", {226, 134, 177, 0}}, {(unsigned char*)"rsqb", {93, 0}}, {(unsigned char*)"rsquo", {226, 128, 153, 0}}, {(unsigned char*)"rsquor", {226, 128, 153, 0}}, {(unsigned char*)"rthree", {226, 139, 140, 0}}, {(unsigned char*)"rtimes", {226, 139, 138, 0}}, {(unsigned char*)"rtri", {226, 150, 185, 0}}, {(unsigned char*)"rtrie", {226, 138, 181, 0}}, {(unsigned char*)"rtrif", {226, 150, 184, 0}}, {(unsigned char*)"rtriltri", {226, 167, 142, 0}}, {(unsigned char*)"ruluhar", {226, 165, 168, 0}}, {(unsigned char*)"rx", {226, 132, 158, 0}}, {(unsigned char*)"sacute", {197, 155, 0}}, {(unsigned char*)"sbquo", {226, 128, 154, 0}}, {(unsigned char*)"sc", {226, 137, 187, 0}}, {(unsigned char*)"scE", {226, 170, 180, 0}}, {(unsigned char*)"scap", {226, 170, 184, 0}}, {(unsigned char*)"scaron", {197, 161, 0}}, {(unsigned char*)"sccue", {226, 137, 189, 0}}, {(unsigned char*)"sce", {226, 170, 176, 0}}, {(unsigned char*)"scedil", {197, 159, 0}}, {(unsigned char*)"scirc", {197, 157, 0}}, {(unsigned char*)"scnE", {226, 170, 182, 0}}, {(unsigned char*)"scnap", {226, 170, 186, 0}}, {(unsigned char*)"scnsim", {226, 139, 169, 0}}, {(unsigned char*)"scpolint", {226, 168, 147, 0}}, {(unsigned char*)"scsim", {226, 137, 191, 0}}, {(unsigned char*)"scy", {209, 129, 0}}, {(unsigned char*)"sdot", {226, 139, 133, 0}}, {(unsigned char*)"sdotb", {226, 138, 161, 0}}, {(unsigned char*)"sdote", {226, 169, 166, 0}}, {(unsigned char*)"seArr", {226, 135, 152, 0}}, {(unsigned char*)"searhk", {226, 164, 165, 0}}, {(unsigned char*)"searr", {226, 134, 152, 0}}, {(unsigned char*)"searrow", {226, 134, 152, 0}}, {(unsigned char*)"sect", {194, 167, 0}}, {(unsigned char*)"semi", {59, 0}}, {(unsigned char*)"seswar", {226, 164, 169, 0}}, {(unsigned char*)"setminus", {226, 136, 150, 0}}, {(unsigned char*)"setmn", {226, 136, 150, 0}}, {(unsigned char*)"sext", {226, 156, 182, 0}}, {(unsigned char*)"sfr", {240, 157, 148, 176, 0}}, {(unsigned char*)"sfrown", {226, 140, 162, 0}}, {(unsigned char*)"sharp", {226, 153, 175, 0}}, {(unsigned char*)"shchcy", {209, 137, 0}}, {(unsigned char*)"shcy", {209, 136, 0}}, {(unsigned char*)"shortmid", {226, 136, 163, 0}}, {(unsigned char*)"shortparallel", {226, 136, 165, 0}}, {(unsigned char*)"shy", {194, 173, 0}}, {(unsigned char*)"sigma", {207, 131, 0}}, {(unsigned char*)"sigmaf", {207, 130, 0}}, {(unsigned char*)"sigmav", {207, 130, 0}}, {(unsigned char*)"sim", {226, 136, 188, 0}}, {(unsigned char*)"simdot", {226, 169, 170, 0}}, {(unsigned char*)"sime", {226, 137, 131, 0}}, {(unsigned char*)"simeq", {226, 137, 131, 0}}, {(unsigned char*)"simg", {226, 170, 158, 0}}, {(unsigned char*)"simgE", {226, 170, 160, 0}}, {(unsigned char*)"siml", {226, 170, 157, 0}}, {(unsigned char*)"simlE", {226, 170, 159, 0}}, {(unsigned char*)"simne", {226, 137, 134, 0}}, {(unsigned char*)"simplus", {226, 168, 164, 0}}, {(unsigned char*)"simrarr", {226, 165, 178, 0}}, {(unsigned char*)"slarr", {226, 134, 144, 0}}, {(unsigned char*)"smallsetminus", {226, 136, 150, 0}}, {(unsigned char*)"smashp", {226, 168, 179, 0}}, {(unsigned char*)"smeparsl", {226, 167, 164, 0}}, {(unsigned char*)"smid", {226, 136, 163, 0}}, {(unsigned char*)"smile", {226, 140, 163, 0}}, {(unsigned char*)"smt", {226, 170, 170, 0}}, {(unsigned char*)"smte", {226, 170, 172, 0}}, {(unsigned char*)"smtes", {226, 170, 172, 239, 184, 128, 0}}, {(unsigned char*)"softcy", {209, 140, 0}}, {(unsigned char*)"sol", {47, 0}}, {(unsigned char*)"solb", {226, 167, 132, 0}}, {(unsigned char*)"solbar", {226, 140, 191, 0}}, {(unsigned char*)"sopf", {240, 157, 149, 164, 0}}, {(unsigned char*)"spades", {226, 153, 160, 0}}, {(unsigned char*)"spadesuit", {226, 153, 160, 0}}, {(unsigned char*)"spar", {226, 136, 165, 0}}, {(unsigned char*)"sqcap", {226, 138, 147, 0}}, {(unsigned char*)"sqcaps", {226, 138, 147, 239, 184, 128, 0}}, {(unsigned char*)"sqcup", {226, 138, 148, 0}}, {(unsigned char*)"sqcups", {226, 138, 148, 239, 184, 128, 0}}, {(unsigned char*)"sqsub", {226, 138, 143, 0}}, {(unsigned char*)"sqsube", {226, 138, 145, 0}}, {(unsigned char*)"sqsubset", {226, 138, 143, 0}}, {(unsigned char*)"sqsubseteq", {226, 138, 145, 0}}, {(unsigned char*)"sqsup", {226, 138, 144, 0}}, {(unsigned char*)"sqsupe", {226, 138, 146, 0}}, {(unsigned char*)"sqsupset", {226, 138, 144, 0}}, {(unsigned char*)"sqsupseteq", {226, 138, 146, 0}}, {(unsigned char*)"squ", {226, 150, 161, 0}}, {(unsigned char*)"square", {226, 150, 161, 0}}, {(unsigned char*)"squarf", {226, 150, 170, 0}}, {(unsigned char*)"squf", {226, 150, 170, 0}}, {(unsigned char*)"srarr", {226, 134, 146, 0}}, {(unsigned char*)"sscr", {240, 157, 147, 136, 0}}, {(unsigned char*)"ssetmn", {226, 136, 150, 0}}, {(unsigned char*)"ssmile", {226, 140, 163, 0}}, {(unsigned char*)"sstarf", {226, 139, 134, 0}}, {(unsigned char*)"star", {226, 152, 134, 0}}, {(unsigned char*)"starf", {226, 152, 133, 0}}, {(unsigned char*)"straightepsilon", {207, 181, 0}}, {(unsigned char*)"straightphi", {207, 149, 0}}, {(unsigned char*)"strns", {194, 175, 0}}, {(unsigned char*)"sub", {226, 138, 130, 0}}, {(unsigned char*)"subE", {226, 171, 133, 0}}, {(unsigned char*)"subdot", {226, 170, 189, 0}}, {(unsigned char*)"sube", {226, 138, 134, 0}}, {(unsigned char*)"subedot", {226, 171, 131, 0}}, {(unsigned char*)"submult", {226, 171, 129, 0}}, {(unsigned char*)"subnE", {226, 171, 139, 0}}, {(unsigned char*)"subne", {226, 138, 138, 0}}, {(unsigned char*)"subplus", {226, 170, 191, 0}}, {(unsigned char*)"subrarr", {226, 165, 185, 0}}, {(unsigned char*)"subset", {226, 138, 130, 0}}, {(unsigned char*)"subseteq", {226, 138, 134, 0}}, {(unsigned char*)"subseteqq", {226, 171, 133, 0}}, {(unsigned char*)"subsetneq", {226, 138, 138, 0}}, {(unsigned char*)"subsetneqq", {226, 171, 139, 0}}, {(unsigned char*)"subsim", {226, 171, 135, 0}}, {(unsigned char*)"subsub", {226, 171, 149, 0}}, {(unsigned char*)"subsup", {226, 171, 147, 0}}, {(unsigned char*)"succ", {226, 137, 187, 0}}, {(unsigned char*)"succapprox", {226, 170, 184, 0}}, {(unsigned char*)"succcurlyeq", {226, 137, 189, 0}}, {(unsigned char*)"succeq", {226, 170, 176, 0}}, {(unsigned char*)"succnapprox", {226, 170, 186, 0}}, {(unsigned char*)"succneqq", {226, 170, 182, 0}}, {(unsigned char*)"succnsim", {226, 139, 169, 0}}, {(unsigned char*)"succsim", {226, 137, 191, 0}}, {(unsigned char*)"sum", {226, 136, 145, 0}}, {(unsigned char*)"sung", {226, 153, 170, 0}}, {(unsigned char*)"sup", {226, 138, 131, 0}}, {(unsigned char*)"sup1", {194, 185, 0}}, {(unsigned char*)"sup2", {194, 178, 0}}, {(unsigned char*)"sup3", {194, 179, 0}}, {(unsigned char*)"supE", {226, 171, 134, 0}}, {(unsigned char*)"supdot", {226, 170, 190, 0}}, {(unsigned char*)"supdsub", {226, 171, 152, 0}}, {(unsigned char*)"supe", {226, 138, 135, 0}}, {(unsigned char*)"supedot", {226, 171, 132, 0}}, {(unsigned char*)"suphsol", {226, 159, 137, 0}}, {(unsigned char*)"suphsub", {226, 171, 151, 0}}, {(unsigned char*)"suplarr", {226, 165, 187, 0}}, {(unsigned char*)"supmult", {226, 171, 130, 0}}, {(unsigned char*)"supnE", {226, 171, 140, 0}}, {(unsigned char*)"supne", {226, 138, 139, 0}}, {(unsigned char*)"supplus", {226, 171, 128, 0}}, {(unsigned char*)"supset", {226, 138, 131, 0}}, {(unsigned char*)"supseteq", {226, 138, 135, 0}}, {(unsigned char*)"supseteqq", {226, 171, 134, 0}}, {(unsigned char*)"supsetneq", {226, 138, 139, 0}}, {(unsigned char*)"supsetneqq", {226, 171, 140, 0}}, {(unsigned char*)"supsim", {226, 171, 136, 0}}, {(unsigned char*)"supsub", {226, 171, 148, 0}}, {(unsigned char*)"supsup", {226, 171, 150, 0}}, {(unsigned char*)"swArr", {226, 135, 153, 0}}, {(unsigned char*)"swarhk", {226, 164, 166, 0}}, {(unsigned char*)"swarr", {226, 134, 153, 0}}, {(unsigned char*)"swarrow", {226, 134, 153, 0}}, {(unsigned char*)"swnwar", {226, 164, 170, 0}}, {(unsigned char*)"szlig", {195, 159, 0}}, {(unsigned char*)"target", {226, 140, 150, 0}}, {(unsigned char*)"tau", {207, 132, 0}}, {(unsigned char*)"tbrk", {226, 142, 180, 0}}, {(unsigned char*)"tcaron", {197, 165, 0}}, {(unsigned char*)"tcedil", {197, 163, 0}}, {(unsigned char*)"tcy", {209, 130, 0}}, {(unsigned char*)"tdot", {226, 131, 155, 0}}, {(unsigned char*)"telrec", {226, 140, 149, 0}}, {(unsigned char*)"tfr", {240, 157, 148, 177, 0}}, {(unsigned char*)"there4", {226, 136, 180, 0}}, {(unsigned char*)"therefore", {226, 136, 180, 0}}, {(unsigned char*)"theta", {206, 184, 0}}, {(unsigned char*)"thetasym", {207, 145, 0}}, {(unsigned char*)"thetav", {207, 145, 0}}, {(unsigned char*)"thickapprox", {226, 137, 136, 0}}, {(unsigned char*)"thicksim", {226, 136, 188, 0}}, {(unsigned char*)"thinsp", {226, 128, 137, 0}}, {(unsigned char*)"thkap", {226, 137, 136, 0}}, {(unsigned char*)"thksim", {226, 136, 188, 0}}, {(unsigned char*)"thorn", {195, 190, 0}}, {(unsigned char*)"tilde", {203, 156, 0}}, {(unsigned char*)"times", {195, 151, 0}}, {(unsigned char*)"timesb", {226, 138, 160, 0}}, {(unsigned char*)"timesbar", {226, 168, 177, 0}}, {(unsigned char*)"timesd", {226, 168, 176, 0}}, {(unsigned char*)"tint", {226, 136, 173, 0}}, {(unsigned char*)"toea", {226, 164, 168, 0}}, {(unsigned char*)"top", {226, 138, 164, 0}}, {(unsigned char*)"topbot", {226, 140, 182, 0}}, {(unsigned char*)"topcir", {226, 171, 177, 0}}, {(unsigned char*)"topf", {240, 157, 149, 165, 0}}, {(unsigned char*)"topfork", {226, 171, 154, 0}}, {(unsigned char*)"tosa", {226, 164, 169, 0}}, {(unsigned char*)"tprime", {226, 128, 180, 0}}, {(unsigned char*)"trade", {226, 132, 162, 0}}, {(unsigned char*)"triangle", {226, 150, 181, 0}}, {(unsigned char*)"triangledown", {226, 150, 191, 0}}, {(unsigned char*)"triangleleft", {226, 151, 131, 0}}, {(unsigned char*)"trianglelefteq", {226, 138, 180, 0}}, {(unsigned char*)"triangleq", {226, 137, 156, 0}}, {(unsigned char*)"triangleright", {226, 150, 185, 0}}, {(unsigned char*)"trianglerighteq", {226, 138, 181, 0}}, {(unsigned char*)"tridot", {226, 151, 172, 0}}, {(unsigned char*)"trie", {226, 137, 156, 0}}, {(unsigned char*)"triminus", {226, 168, 186, 0}}, {(unsigned char*)"triplus", {226, 168, 185, 0}}, {(unsigned char*)"trisb", {226, 167, 141, 0}}, {(unsigned char*)"tritime", {226, 168, 187, 0}}, {(unsigned char*)"trpezium", {226, 143, 162, 0}}, {(unsigned char*)"tscr", {240, 157, 147, 137, 0}}, {(unsigned char*)"tscy", {209, 134, 0}}, {(unsigned char*)"tshcy", {209, 155, 0}}, {(unsigned char*)"tstrok", {197, 167, 0}}, {(unsigned char*)"twixt", {226, 137, 172, 0}}, {(unsigned char*)"twoheadleftarrow", {226, 134, 158, 0}}, {(unsigned char*)"twoheadrightarrow", {226, 134, 160, 0}}, {(unsigned char*)"uArr", {226, 135, 145, 0}}, {(unsigned char*)"uHar", {226, 165, 163, 0}}, {(unsigned char*)"uacute", {195, 186, 0}}, {(unsigned char*)"uarr", {226, 134, 145, 0}}, {(unsigned char*)"ubrcy", {209, 158, 0}}, {(unsigned char*)"ubreve", {197, 173, 0}}, {(unsigned char*)"ucirc", {195, 187, 0}}, {(unsigned char*)"ucy", {209, 131, 0}}, {(unsigned char*)"udarr", {226, 135, 133, 0}}, {(unsigned char*)"udblac", {197, 177, 0}}, {(unsigned char*)"udhar", {226, 165, 174, 0}}, {(unsigned char*)"ufisht", {226, 165, 190, 0}}, {(unsigned char*)"ufr", {240, 157, 148, 178, 0}}, {(unsigned char*)"ugrave", {195, 185, 0}}, {(unsigned char*)"uharl", {226, 134, 191, 0}}, {(unsigned char*)"uharr", {226, 134, 190, 0}}, {(unsigned char*)"uhblk", {226, 150, 128, 0}}, {(unsigned char*)"ulcorn", {226, 140, 156, 0}}, {(unsigned char*)"ulcorner", {226, 140, 156, 0}}, {(unsigned char*)"ulcrop", {226, 140, 143, 0}}, {(unsigned char*)"ultri", {226, 151, 184, 0}}, {(unsigned char*)"umacr", {197, 171, 0}}, {(unsigned char*)"uml", {194, 168, 0}}, {(unsigned char*)"uogon", {197, 179, 0}}, {(unsigned char*)"uopf", {240, 157, 149, 166, 0}}, {(unsigned char*)"uparrow", {226, 134, 145, 0}}, {(unsigned char*)"updownarrow", {226, 134, 149, 0}}, {(unsigned char*)"upharpoonleft", {226, 134, 191, 0}}, {(unsigned char*)"upharpoonright", {226, 134, 190, 0}}, {(unsigned char*)"uplus", {226, 138, 142, 0}}, {(unsigned char*)"upsi", {207, 133, 0}}, {(unsigned char*)"upsih", {207, 146, 0}}, {(unsigned char*)"upsilon", {207, 133, 0}}, {(unsigned char*)"upuparrows", {226, 135, 136, 0}}, {(unsigned char*)"urcorn", {226, 140, 157, 0}}, {(unsigned char*)"urcorner", {226, 140, 157, 0}}, {(unsigned char*)"urcrop", {226, 140, 142, 0}}, {(unsigned char*)"uring", {197, 175, 0}}, {(unsigned char*)"urtri", {226, 151, 185, 0}}, {(unsigned char*)"uscr", {240, 157, 147, 138, 0}}, {(unsigned char*)"utdot", {226, 139, 176, 0}}, {(unsigned char*)"utilde", {197, 169, 0}}, {(unsigned char*)"utri", {226, 150, 181, 0}}, {(unsigned char*)"utrif", {226, 150, 180, 0}}, {(unsigned char*)"uuarr", {226, 135, 136, 0}}, {(unsigned char*)"uuml", {195, 188, 0}}, {(unsigned char*)"uwangle", {226, 166, 167, 0}}, {(unsigned char*)"vArr", {226, 135, 149, 0}}, {(unsigned char*)"vBar", {226, 171, 168, 0}}, {(unsigned char*)"vBarv", {226, 171, 169, 0}}, {(unsigned char*)"vDash", {226, 138, 168, 0}}, {(unsigned char*)"vangrt", {226, 166, 156, 0}}, {(unsigned char*)"varepsilon", {207, 181, 0}}, {(unsigned char*)"varkappa", {207, 176, 0}}, {(unsigned char*)"varnothing", {226, 136, 133, 0}}, {(unsigned char*)"varphi", {207, 149, 0}}, {(unsigned char*)"varpi", {207, 150, 0}}, {(unsigned char*)"varpropto", {226, 136, 157, 0}}, {(unsigned char*)"varr", {226, 134, 149, 0}}, {(unsigned char*)"varrho", {207, 177, 0}}, {(unsigned char*)"varsigma", {207, 130, 0}}, {(unsigned char*)"varsubsetneq", {226, 138, 138, 239, 184, 128, 0}}, {(unsigned char*)"varsubsetneqq", {226, 171, 139, 239, 184, 128, 0}}, {(unsigned char*)"varsupsetneq", {226, 138, 139, 239, 184, 128, 0}}, {(unsigned char*)"varsupsetneqq", {226, 171, 140, 239, 184, 128, 0}}, {(unsigned char*)"vartheta", {207, 145, 0}}, {(unsigned char*)"vartriangleleft", {226, 138, 178, 0}}, {(unsigned char*)"vartriangleright", {226, 138, 179, 0}}, {(unsigned char*)"vcy", {208, 178, 0}}, {(unsigned char*)"vdash", {226, 138, 162, 0}}, {(unsigned char*)"vee", {226, 136, 168, 0}}, {(unsigned char*)"veebar", {226, 138, 187, 0}}, {(unsigned char*)"veeeq", {226, 137, 154, 0}}, {(unsigned char*)"vellip", {226, 139, 174, 0}}, {(unsigned char*)"verbar", {124, 0}}, {(unsigned char*)"vert", {124, 0}}, {(unsigned char*)"vfr", {240, 157, 148, 179, 0}}, {(unsigned char*)"vltri", {226, 138, 178, 0}}, {(unsigned char*)"vnsub", {226, 138, 130, 226, 131, 146, 0}}, {(unsigned char*)"vnsup", {226, 138, 131, 226, 131, 146, 0}}, {(unsigned char*)"vopf", {240, 157, 149, 167, 0}}, {(unsigned char*)"vprop", {226, 136, 157, 0}}, {(unsigned char*)"vrtri", {226, 138, 179, 0}}, {(unsigned char*)"vscr", {240, 157, 147, 139, 0}}, {(unsigned char*)"vsubnE", {226, 171, 139, 239, 184, 128, 0}}, {(unsigned char*)"vsubne", {226, 138, 138, 239, 184, 128, 0}}, {(unsigned char*)"vsupnE", {226, 171, 140, 239, 184, 128, 0}}, {(unsigned char*)"vsupne", {226, 138, 139, 239, 184, 128, 0}}, {(unsigned char*)"vzigzag", {226, 166, 154, 0}}, {(unsigned char*)"wcirc", {197, 181, 0}}, {(unsigned char*)"wedbar", {226, 169, 159, 0}}, {(unsigned char*)"wedge", {226, 136, 167, 0}}, {(unsigned char*)"wedgeq", {226, 137, 153, 0}}, {(unsigned char*)"weierp", {226, 132, 152, 0}}, {(unsigned char*)"wfr", {240, 157, 148, 180, 0}}, {(unsigned char*)"wopf", {240, 157, 149, 168, 0}}, {(unsigned char*)"wp", {226, 132, 152, 0}}, {(unsigned char*)"wr", {226, 137, 128, 0}}, {(unsigned char*)"wreath", {226, 137, 128, 0}}, {(unsigned char*)"wscr", {240, 157, 147, 140, 0}}, {(unsigned char*)"xcap", {226, 139, 130, 0}}, {(unsigned char*)"xcirc", {226, 151, 175, 0}}, {(unsigned char*)"xcup", {226, 139, 131, 0}}, {(unsigned char*)"xdtri", {226, 150, 189, 0}}, {(unsigned char*)"xfr", {240, 157, 148, 181, 0}}, {(unsigned char*)"xhArr", {226, 159, 186, 0}}, {(unsigned char*)"xharr", {226, 159, 183, 0}}, {(unsigned char*)"xi", {206, 190, 0}}, {(unsigned char*)"xlArr", {226, 159, 184, 0}}, {(unsigned char*)"xlarr", {226, 159, 181, 0}}, {(unsigned char*)"xmap", {226, 159, 188, 0}}, {(unsigned char*)"xnis", {226, 139, 187, 0}}, {(unsigned char*)"xodot", {226, 168, 128, 0}}, {(unsigned char*)"xopf", {240, 157, 149, 169, 0}}, {(unsigned char*)"xoplus", {226, 168, 129, 0}}, {(unsigned char*)"xotime", {226, 168, 130, 0}}, {(unsigned char*)"xrArr", {226, 159, 185, 0}}, {(unsigned char*)"xrarr", {226, 159, 182, 0}}, {(unsigned char*)"xscr", {240, 157, 147, 141, 0}}, {(unsigned char*)"xsqcup", {226, 168, 134, 0}}, {(unsigned char*)"xuplus", {226, 168, 132, 0}}, {(unsigned char*)"xutri", {226, 150, 179, 0}}, {(unsigned char*)"xvee", {226, 139, 129, 0}}, {(unsigned char*)"xwedge", {226, 139, 128, 0}}, {(unsigned char*)"yacute", {195, 189, 0}}, {(unsigned char*)"yacy", {209, 143, 0}}, {(unsigned char*)"ycirc", {197, 183, 0}}, {(unsigned char*)"ycy", {209, 139, 0}}, {(unsigned char*)"yen", {194, 165, 0}}, {(unsigned char*)"yfr", {240, 157, 148, 182, 0}}, {(unsigned char*)"yicy", {209, 151, 0}}, {(unsigned char*)"yopf", {240, 157, 149, 170, 0}}, {(unsigned char*)"yscr", {240, 157, 147, 142, 0}}, {(unsigned char*)"yucy", {209, 142, 0}}, {(unsigned char*)"yuml", {195, 191, 0}}, {(unsigned char*)"zacute", {197, 186, 0}}, {(unsigned char*)"zcaron", {197, 190, 0}}, {(unsigned char*)"zcy", {208, 183, 0}}, {(unsigned char*)"zdot", {197, 188, 0}}, {(unsigned char*)"zeetrf", {226, 132, 168, 0}}, {(unsigned char*)"zeta", {206, 182, 0}}, {(unsigned char*)"zfr", {240, 157, 148, 183, 0}}, {(unsigned char*)"zhcy", {208, 182, 0}}, {(unsigned char*)"zigrarr", {226, 135, 157, 0}}, {(unsigned char*)"zopf", {240, 157, 149, 171, 0}}, {(unsigned char*)"zscr", {240, 157, 147, 143, 0}}, {(unsigned char*)"zwj", {226, 128, 141, 0}}, {(unsigned char*)"zwnj", {226, 128, 140, 0}}, }; ��������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/cmark-gfm-extension_api.h�����������������������������������������������������0000644�0000000�0000000�00000065053�13442034251�017545� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_EXTENSION_API_H #define CMARK_GFM_EXTENSION_API_H #ifdef __cplusplus extern "C" { #endif #include "cmark-gfm.h" struct cmark_renderer; struct cmark_html_renderer; struct cmark_chunk; /** * ## Extension Support * * While the "core" of libcmark is strictly compliant with the * specification, an API is provided for extension writers to * hook into the parsing process. * * It should be noted that the cmark_node API already offers * room for customization, with methods offered to traverse and * modify the AST, and even define custom blocks. * When the desired customization is achievable in an error-proof * way using that API, it should be the preferred method. * * The following API requires a more in-depth understanding * of libcmark's parsing strategy, which is exposed * [here](http://spec.commonmark.org/0.24/#appendix-a-parsing-strategy). * * It should be used when "a posteriori" modification of the AST * proves to be too difficult / impossible to implement correctly. * * It can also serve as an intermediary step before extending * the specification, as an extension implemented using this API * will be trivially integrated in the core if it proves to be * desirable. */ typedef struct cmark_plugin cmark_plugin; /** A syntax extension that can be attached to a cmark_parser * with cmark_parser_attach_syntax_extension(). * * Extension writers should assign functions matching * the signature of the following 'virtual methods' to * implement new functionality. * * Their calling order and expected behaviour match the procedure outlined * at <http://spec.commonmark.org/0.24/#phase-1-block-structure>: * * During step 1, cmark will call the function provided through * 'cmark_syntax_extension_set_match_block_func' when it * iterates over an open block created by this extension, * to determine whether it could contain the new line. * If no function was provided, cmark will close the block. * * During step 2, if and only if the new line doesn't match any * of the standard syntax rules, cmark will call the function * provided through 'cmark_syntax_extension_set_open_block_func' * to let the extension determine whether that new line matches * one of its syntax rules. * It is the responsibility of the parser to create and add the * new block with cmark_parser_make_block and cmark_parser_add_child. * If no function was provided is NULL, the extension will have * no effect at all on the final block structure of the AST. * * #### Inline parsing phase hooks * * For each character provided by the extension through * 'cmark_syntax_extension_set_special_inline_chars', * the function provided by the extension through * 'cmark_syntax_extension_set_match_inline_func' * will get called, it is the responsibility of the extension * to scan the characters located at the current inline parsing offset * with the cmark_inline_parser API. * * Depending on the type of the extension, it can either: * * * Scan forward, determine that the syntax matches and return * a newly-created inline node with the appropriate type. * This is the technique that would be used if inline code * (with backticks) was implemented as an extension. * * Scan only the character(s) that its syntax rules require * for opening and closing nodes, push a delimiter on the * delimiter stack, and return a simple text node with its * contents set to the character(s) consumed. * This is the technique that would be used if emphasis * inlines were implemented as an extension. * * When an extension has pushed delimiters on the stack, * the function provided through * 'cmark_syntax_extension_set_inline_from_delim_func' * will get called in a latter phase, * when the inline parser has matched opener and closer delimiters * created by the extension together. * * It is then the responsibility of the extension to modify * and populate the opener inline text node, and to remove * the necessary delimiters from the delimiter stack. * * Finally, the extension should return NULL if its scan didn't * match its syntax rules. * * The extension can store whatever private data it might need * with 'cmark_syntax_extension_set_private', * and optionally define a free function for this data. */ typedef struct subject cmark_inline_parser; /** Exposed raw for now */ typedef struct delimiter { struct delimiter *previous; struct delimiter *next; cmark_node *inl_text; bufsize_t length; unsigned char delim_char; int can_open; int can_close; } delimiter; /** * ### Plugin API. * * Extensions should be distributed as dynamic libraries, * with a single exported function named after the distributed * filename. * * When discovering extensions (see cmark_init), cmark will * try to load a symbol named "init_{{filename}}" in all the * dynamic libraries it encounters. * * For example, given a dynamic library named myextension.so * (or myextension.dll), cmark will try to load the symbol * named "init_myextension". This means that the filename * must lend itself to forming a valid C identifier, with * the notable exception of dashes, which will be translated * to underscores, which means cmark will look for a function * named "init_my_extension" if it encounters a dynamic library * named "my-extension.so". * * See the 'cmark_plugin_init_func' typedef for the exact prototype * this function should follow. * * For now the extensibility of cmark is not complete, as * it only offers API to hook into the block parsing phase * (<http://spec.commonmark.org/0.24/#phase-1-block-structure>). * * See 'cmark_plugin_register_syntax_extension' for more information. */ /** The prototype plugins' init function should follow. */ typedef int (*cmark_plugin_init_func)(cmark_plugin *plugin); /** Register a syntax 'extension' with the 'plugin', it will be made * available as an extension and, if attached to a cmark_parser * with 'cmark_parser_attach_syntax_extension', it will contribute * to the block parsing process. * * See the documentation for 'cmark_syntax_extension' for information * on how to implement one. * * This function will typically be called from the init function * of external modules. * * This takes ownership of 'extension', one should not call * 'cmark_syntax_extension_free' on a registered extension. */ CMARK_GFM_EXPORT int cmark_plugin_register_syntax_extension(cmark_plugin *plugin, cmark_syntax_extension *extension); /** This will search for the syntax extension named 'name' among the * registered syntax extensions. * * It can then be attached to a cmark_parser * with the cmark_parser_attach_syntax_extension method. */ CMARK_GFM_EXPORT cmark_syntax_extension *cmark_find_syntax_extension(const char *name); /** Should create and add a new open block to 'parent_container' if * 'input' matches a syntax rule for that block type. It is allowed * to modify the type of 'parent_container'. * * Should return the newly created block if there is one, or * 'parent_container' if its type was modified, or NULL. */ typedef cmark_node * (*cmark_open_block_func) (cmark_syntax_extension *extension, int indented, cmark_parser *parser, cmark_node *parent_container, unsigned char *input, int len); typedef cmark_node *(*cmark_match_inline_func)(cmark_syntax_extension *extension, cmark_parser *parser, cmark_node *parent, unsigned char character, cmark_inline_parser *inline_parser); typedef delimiter *(*cmark_inline_from_delim_func)(cmark_syntax_extension *extension, cmark_parser *parser, cmark_inline_parser *inline_parser, delimiter *opener, delimiter *closer); /** Should return 'true' if 'input' can be contained in 'container', * 'false' otherwise. */ typedef int (*cmark_match_block_func) (cmark_syntax_extension *extension, cmark_parser *parser, unsigned char *input, int len, cmark_node *container); typedef const char *(*cmark_get_type_string_func) (cmark_syntax_extension *extension, cmark_node *node); typedef int (*cmark_can_contain_func) (cmark_syntax_extension *extension, cmark_node *node, cmark_node_type child); typedef int (*cmark_contains_inlines_func) (cmark_syntax_extension *extension, cmark_node *node); typedef void (*cmark_common_render_func) (cmark_syntax_extension *extension, struct cmark_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options); typedef int (*cmark_commonmark_escape_func) (cmark_syntax_extension *extension, cmark_node *node, int c); typedef const char* (*cmark_xml_attr_func) (cmark_syntax_extension *extension, cmark_node *node); typedef void (*cmark_html_render_func) (cmark_syntax_extension *extension, struct cmark_html_renderer *renderer, cmark_node *node, cmark_event_type ev_type, int options); typedef int (*cmark_html_filter_func) (cmark_syntax_extension *extension, const unsigned char *tag, size_t tag_len); typedef cmark_node *(*cmark_postprocess_func) (cmark_syntax_extension *extension, cmark_parser *parser, cmark_node *root); typedef int (*cmark_ispunct_func) (char c); typedef void (*cmark_opaque_alloc_func) (cmark_syntax_extension *extension, cmark_mem *mem, cmark_node *node); typedef void (*cmark_opaque_free_func) (cmark_syntax_extension *extension, cmark_mem *mem, cmark_node *node); /** Free a cmark_syntax_extension. */ CMARK_GFM_EXPORT void cmark_syntax_extension_free (cmark_mem *mem, cmark_syntax_extension *extension); /** Return a newly-constructed cmark_syntax_extension, named 'name'. */ CMARK_GFM_EXPORT cmark_syntax_extension *cmark_syntax_extension_new (const char *name); CMARK_GFM_EXPORT cmark_node_type cmark_syntax_extension_add_node(int is_inline); CMARK_GFM_EXPORT void cmark_syntax_extension_set_emphasis(cmark_syntax_extension *extension, int emphasis); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_open_block_func(cmark_syntax_extension *extension, cmark_open_block_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_match_block_func(cmark_syntax_extension *extension, cmark_match_block_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_match_inline_func(cmark_syntax_extension *extension, cmark_match_inline_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_inline_from_delim_func(cmark_syntax_extension *extension, cmark_inline_from_delim_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_special_inline_chars(cmark_syntax_extension *extension, cmark_llist *special_chars); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_get_type_string_func(cmark_syntax_extension *extension, cmark_get_type_string_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_can_contain_func(cmark_syntax_extension *extension, cmark_can_contain_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_contains_inlines_func(cmark_syntax_extension *extension, cmark_contains_inlines_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_commonmark_render_func(cmark_syntax_extension *extension, cmark_common_render_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_plaintext_render_func(cmark_syntax_extension *extension, cmark_common_render_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_latex_render_func(cmark_syntax_extension *extension, cmark_common_render_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_xml_attr_func(cmark_syntax_extension *extension, cmark_xml_attr_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_man_render_func(cmark_syntax_extension *extension, cmark_common_render_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_html_render_func(cmark_syntax_extension *extension, cmark_html_render_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_html_filter_func(cmark_syntax_extension *extension, cmark_html_filter_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_commonmark_escape_func(cmark_syntax_extension *extension, cmark_commonmark_escape_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_private(cmark_syntax_extension *extension, void *priv, cmark_free_func free_func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void *cmark_syntax_extension_get_private(cmark_syntax_extension *extension); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_postprocess_func(cmark_syntax_extension *extension, cmark_postprocess_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_opaque_alloc_func(cmark_syntax_extension *extension, cmark_opaque_alloc_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_syntax_extension_set_opaque_free_func(cmark_syntax_extension *extension, cmark_opaque_free_func func); /** See the documentation for 'cmark_syntax_extension' */ CMARK_GFM_EXPORT void cmark_parser_set_backslash_ispunct_func(cmark_parser *parser, cmark_ispunct_func func); /** Return the index of the line currently being parsed, starting with 1. */ CMARK_GFM_EXPORT int cmark_parser_get_line_number(cmark_parser *parser); /** Return the offset in bytes in the line being processed. * * Example: * * ### foo * * Here, offset will first be 0, then 5 (the index of the 'f' character). */ CMARK_GFM_EXPORT int cmark_parser_get_offset(cmark_parser *parser); /** * Return the offset in 'columns' in the line being processed. * * This value may differ from the value returned by * cmark_parser_get_offset() in that it accounts for tabs, * and as such should not be used as an index in the current line's * buffer. * * Example: * * cmark_parser_advance_offset() can be called to advance the * offset by a number of columns, instead of a number of bytes. * * In that case, if offset falls "in the middle" of a tab * character, 'column' and offset will differ. * * ``` * foo \t bar * ^ ^^ * offset (0) 20 * ``` * * If cmark_parser_advance_offset is called here with 'columns' * set to 'true' and 'offset' set to 22, cmark_parser_get_offset() * will return 20, whereas cmark_parser_get_column() will return * 22. * * Additionally, as tabs expand to the next multiple of 4 column, * cmark_parser_has_partially_consumed_tab() will now return * 'true'. */ CMARK_GFM_EXPORT int cmark_parser_get_column(cmark_parser *parser); /** Return the absolute index in bytes of the first nonspace * character coming after the offset as returned by * cmark_parser_get_offset() in the line currently being processed. * * Example: * * ``` * foo bar baz \n * ^ ^ ^ * 0 offset (16) first_nonspace (28) * ``` */ CMARK_GFM_EXPORT int cmark_parser_get_first_nonspace(cmark_parser *parser); /** Return the absolute index of the first nonspace column coming after 'offset' * in the line currently being processed, counting tabs as multiple * columns as appropriate. * * See the documentation for cmark_parser_get_first_nonspace() and * cmark_parser_get_column() for more information. */ CMARK_GFM_EXPORT int cmark_parser_get_first_nonspace_column(cmark_parser *parser); /** Return the difference between the values returned by * cmark_parser_get_first_nonspace_column() and * cmark_parser_get_column(). * * This is not a byte offset, as it can count one tab as multiple * characters. */ CMARK_GFM_EXPORT int cmark_parser_get_indent(cmark_parser *parser); /** Return 'true' if the line currently being processed has been entirely * consumed, 'false' otherwise. * * Example: * * ``` * foo bar baz \n * ^ * offset * ``` * * This function will return 'false' here. * * ``` * foo bar baz \n * ^ * offset * ``` * This function will still return 'false'. * * ``` * foo bar baz \n * ^ * offset * ``` * * At this point, this function will now return 'true'. */ CMARK_GFM_EXPORT int cmark_parser_is_blank(cmark_parser *parser); /** Return 'true' if the value returned by cmark_parser_get_offset() * is 'inside' an expanded tab. * * See the documentation for cmark_parser_get_column() for more * information. */ CMARK_GFM_EXPORT int cmark_parser_has_partially_consumed_tab(cmark_parser *parser); /** Return the length in bytes of the previously processed line, excluding potential * newline (\n) and carriage return (\r) trailing characters. */ CMARK_GFM_EXPORT int cmark_parser_get_last_line_length(cmark_parser *parser); /** Add a child to 'parent' during the parsing process. * * If 'parent' isn't the kind of node that can accept this child, * this function will back up till it hits a node that can, closing * blocks as appropriate. */ CMARK_GFM_EXPORT cmark_node*cmark_parser_add_child(cmark_parser *parser, cmark_node *parent, cmark_node_type block_type, int start_column); /** Advance the 'offset' of the parser in the current line. * * See the documentation of cmark_parser_get_offset() and * cmark_parser_get_column() for more information. */ CMARK_GFM_EXPORT void cmark_parser_advance_offset(cmark_parser *parser, const char *input, int count, int columns); CMARK_GFM_EXPORT void cmark_parser_feed_reentrant(cmark_parser *parser, const char *buffer, size_t len); /** Attach the syntax 'extension' to the 'parser', to provide extra syntax * rules. * See the documentation for cmark_syntax_extension for more information. * * Returns 'true' if the 'extension' was successfully attached, * 'false' otherwise. */ CMARK_GFM_EXPORT int cmark_parser_attach_syntax_extension(cmark_parser *parser, cmark_syntax_extension *extension); /** Change the type of 'node'. * * Return 0 if the type could be changed, 1 otherwise. */ CMARK_GFM_EXPORT int cmark_node_set_type(cmark_node *node, cmark_node_type type); /** Return the string content for all types of 'node'. * The pointer stays valid as long as 'node' isn't freed. */ CMARK_GFM_EXPORT const char *cmark_node_get_string_content(cmark_node *node); /** Set the string 'content' for all types of 'node'. * Copies 'content'. */ CMARK_GFM_EXPORT int cmark_node_set_string_content(cmark_node *node, const char *content); /** Get the syntax extension responsible for the creation of 'node'. * Return NULL if 'node' was created because it matched standard syntax rules. */ CMARK_GFM_EXPORT cmark_syntax_extension *cmark_node_get_syntax_extension(cmark_node *node); /** Set the syntax extension responsible for creating 'node'. */ CMARK_GFM_EXPORT int cmark_node_set_syntax_extension(cmark_node *node, cmark_syntax_extension *extension); /** * ## Inline syntax extension helpers * * The inline parsing process is described in detail at * <http://spec.commonmark.org/0.24/#phase-2-inline-structure> */ /** Should return 'true' if the predicate matches 'c', 'false' otherwise */ typedef int (*cmark_inline_predicate)(int c); /** Advance the current inline parsing offset */ CMARK_GFM_EXPORT void cmark_inline_parser_advance_offset(cmark_inline_parser *parser); /** Get the current inline parsing offset */ CMARK_GFM_EXPORT int cmark_inline_parser_get_offset(cmark_inline_parser *parser); /** Set the offset in bytes in the chunk being processed by the given inline parser. */ CMARK_GFM_EXPORT void cmark_inline_parser_set_offset(cmark_inline_parser *parser, int offset); /** Gets the cmark_chunk being operated on by the given inline parser. * Use cmark_inline_parser_get_offset to get our current position in the chunk. */ CMARK_GFM_EXPORT struct cmark_chunk *cmark_inline_parser_get_chunk(cmark_inline_parser *parser); /** Returns 1 if the inline parser is currently in a bracket; pass 1 for 'image' * if you want to know about an image-type bracket, 0 for link-type. */ CMARK_GFM_EXPORT int cmark_inline_parser_in_bracket(cmark_inline_parser *parser, int image); /** Remove the last n characters from the last child of the given node. * This only works where all n characters are in the single last child, and the last * child is CMARK_NODE_TEXT. */ CMARK_GFM_EXPORT void cmark_node_unput(cmark_node *node, int n); /** Get the character located at the current inline parsing offset */ CMARK_GFM_EXPORT unsigned char cmark_inline_parser_peek_char(cmark_inline_parser *parser); /** Get the character located 'pos' bytes in the current line. */ CMARK_GFM_EXPORT unsigned char cmark_inline_parser_peek_at(cmark_inline_parser *parser, int pos); /** Whether the inline parser has reached the end of the current line */ CMARK_GFM_EXPORT int cmark_inline_parser_is_eof(cmark_inline_parser *parser); /** Get the characters located after the current inline parsing offset * while 'pred' matches. Free after usage. */ CMARK_GFM_EXPORT char *cmark_inline_parser_take_while(cmark_inline_parser *parser, cmark_inline_predicate pred); /** Push a delimiter on the delimiter stack. * See <<http://spec.commonmark.org/0.24/#phase-2-inline-structure> for * more information on the parameters */ CMARK_GFM_EXPORT void cmark_inline_parser_push_delimiter(cmark_inline_parser *parser, unsigned char c, int can_open, int can_close, cmark_node *inl_text); /** Remove 'delim' from the delimiter stack */ CMARK_GFM_EXPORT void cmark_inline_parser_remove_delimiter(cmark_inline_parser *parser, delimiter *delim); CMARK_GFM_EXPORT delimiter *cmark_inline_parser_get_last_delimiter(cmark_inline_parser *parser); CMARK_GFM_EXPORT int cmark_inline_parser_get_line(cmark_inline_parser *parser); CMARK_GFM_EXPORT int cmark_inline_parser_get_column(cmark_inline_parser *parser); /** Convenience function to scan a given delimiter. * * 'left_flanking' and 'right_flanking' will be set to true if they * respectively precede and follow a non-space, non-punctuation * character. * * Additionally, 'punct_before' and 'punct_after' will respectively be set * if the preceding or following character is a punctuation character. * * Note that 'left_flanking' and 'right_flanking' can both be 'true'. * * Returns the number of delimiters encountered, in the limit * of 'max_delims', and advances the inline parsing offset. */ CMARK_GFM_EXPORT int cmark_inline_parser_scan_delimiters(cmark_inline_parser *parser, int max_delims, unsigned char c, int *left_flanking, int *right_flanking, int *punct_before, int *punct_after); CMARK_GFM_EXPORT void cmark_manage_extensions_special_characters(cmark_parser *parser, int add); CMARK_GFM_EXPORT cmark_llist *cmark_parser_get_syntax_extensions(cmark_parser *parser); CMARK_GFM_EXPORT void cmark_arena_push(void); CMARK_GFM_EXPORT int cmark_arena_pop(void); #ifdef __cplusplus } #endif #endif �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/html.h������������������������������������������������������������������������0000644�0000000�0000000�00000001322�13442034251�013767� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_HTML_H #define CMARK_HTML_H #include "buffer.h" #include "node.h" CMARK_INLINE static void cmark_html_render_cr(cmark_strbuf *html) { if (html->size && html->ptr[html->size - 1] != '\n') cmark_strbuf_putc(html, '\n'); } #define BUFFER_SIZE 100 CMARK_INLINE static void cmark_html_render_sourcepos(cmark_node *node, cmark_strbuf *html, int options) { char buffer[BUFFER_SIZE]; if (CMARK_OPT_SOURCEPOS & options) { snprintf(buffer, BUFFER_SIZE, " data-sourcepos=\"%d:%d-%d:%d\"", cmark_node_get_start_line(node), cmark_node_get_start_column(node), cmark_node_get_end_line(node), cmark_node_get_end_column(node)); cmark_strbuf_puts(html, buffer); } } #endif ��������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/plugin.h����������������������������������������������������������������������0000644�0000000�0000000�00000000777�13442034251�014336� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_PLUGIN_H #define CMARK_PLUGIN_H #ifdef __cplusplus extern "C" { #endif #include "cmark-gfm.h" #include "cmark-gfm-extension_api.h" /** * cmark_plugin: * * A plugin structure, which should be filled by plugin's * init functions. */ struct cmark_plugin { cmark_llist *syntax_extensions; }; cmark_llist * cmark_plugin_steal_syntax_extensions(cmark_plugin *plugin); cmark_plugin * cmark_plugin_new(void); void cmark_plugin_free(cmark_plugin *plugin); #ifdef __cplusplus } #endif #endif �cmark-gfm-0.1.8/cbits/registry.h��������������������������������������������������������������������0000644�0000000�0000000�00000000571�13442034251�014700� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_REGISTRY_H #define CMARK_REGISTRY_H #ifdef __cplusplus extern "C" { #endif #include "cmark-gfm.h" #include "plugin.h" CMARK_GFM_EXPORT void cmark_register_plugin(cmark_plugin_init_func reg_fn); CMARK_GFM_EXPORT void cmark_release_plugins(void); CMARK_GFM_EXPORT cmark_llist *cmark_list_syntax_extensions(cmark_mem *mem); #ifdef __cplusplus } #endif #endif ���������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/syntax_extension.h������������������������������������������������������������0000644�0000000�0000000�00000002553�13442034251�016454� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_SYNTAX_EXTENSION_H #define CMARK_SYNTAX_EXTENSION_H #include "cmark-gfm.h" #include "cmark-gfm-extension_api.h" #include "config.h" struct cmark_syntax_extension { cmark_match_block_func last_block_matches; cmark_open_block_func try_opening_block; cmark_match_inline_func match_inline; cmark_inline_from_delim_func insert_inline_from_delim; cmark_llist * special_inline_chars; char * name; void * priv; bool emphasis; cmark_free_func free_function; cmark_get_type_string_func get_type_string_func; cmark_can_contain_func can_contain_func; cmark_contains_inlines_func contains_inlines_func; cmark_common_render_func commonmark_render_func; cmark_common_render_func plaintext_render_func; cmark_common_render_func latex_render_func; cmark_xml_attr_func xml_attr_func; cmark_common_render_func man_render_func; cmark_html_render_func html_render_func; cmark_html_filter_func html_filter_func; cmark_postprocess_func postprocess_func; cmark_opaque_alloc_func opaque_alloc_func; cmark_opaque_free_func opaque_free_func; cmark_commonmark_escape_func commonmark_escape_func; }; #endif �����������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/autolink.h��������������������������������������������������������������������0000644�0000000�0000000�00000000244�13442034251�014653� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_AUTOLINK_H #define CMARK_GFM_AUTOLINK_H #include "cmark-gfm-core-extensions.h" cmark_syntax_extension *create_autolink_extension(void); #endif ������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/cmark-gfm-core-extensions.h���������������������������������������������������0000644�0000000�0000000�00000001317�13442037162�020022� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_CORE_EXTENSIONS_H #define CMARK_GFM_CORE_EXTENSIONS_H #ifdef __cplusplus extern "C" { #endif #include "cmark-gfm-extension_api.h" #include "cmark-gfm-extensions_export.h" #include <stdint.h> CMARK_GFM_EXTENSIONS_EXPORT void cmark_gfm_core_extensions_ensure_registered(void); CMARK_GFM_EXTENSIONS_EXPORT uint16_t cmark_gfm_extensions_get_table_columns(cmark_node *node); CMARK_GFM_EXTENSIONS_EXPORT uint8_t *cmark_gfm_extensions_get_table_alignments(cmark_node *node); CMARK_GFM_EXTENSIONS_EXPORT int cmark_gfm_extensions_get_table_row_is_header(cmark_node *node); CMARK_GFM_EXTENSIONS_EXPORT char *cmark_gfm_extensions_get_tasklist_state(cmark_node *node); #ifdef __cplusplus } #endif #endif �����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/ext_scanners.h����������������������������������������������������������������0000644�0000000�0000000�00000001604�13442037162�015526� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#include "chunk.h" #include "cmark-gfm.h" #ifdef __cplusplus extern "C" { #endif bufsize_t _ext_scan_at(bufsize_t (*scanner)(const unsigned char *), unsigned char *ptr, int len, bufsize_t offset); bufsize_t _scan_table_start(const unsigned char *p); bufsize_t _scan_table_cell(const unsigned char *p); bufsize_t _scan_table_cell_end(const unsigned char *p); bufsize_t _scan_table_row_end(const unsigned char *p); bufsize_t _scan_tasklist(const unsigned char *p); #define scan_table_start(c, l, n) _ext_scan_at(&_scan_table_start, c, l, n) #define scan_table_cell(c, l, n) _ext_scan_at(&_scan_table_cell, c, l, n) #define scan_table_cell_end(c, l, n) _ext_scan_at(&_scan_table_cell_end, c, l, n) #define scan_table_row_end(c, l, n) _ext_scan_at(&_scan_table_row_end, c, l, n) #define scan_tasklist(c, l, n) _ext_scan_at(&_scan_tasklist, c, l, n) #ifdef __cplusplus } #endif ����������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/strikethrough.h���������������������������������������������������������������0000644�0000000�0000000�00000000344�13442034251�015730� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_STRIKETHROUGH_H #define CMARK_GFM_STRIKETHROUGH_H #include "cmark-gfm-core-extensions.h" extern cmark_node_type CMARK_NODE_STRIKETHROUGH; cmark_syntax_extension *create_strikethrough_extension(void); #endif ��������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/table.h�����������������������������������������������������������������������0000644�0000000�0000000�00000000367�13442034251�014122� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_TABLE_H #define CMARK_GFM_TABLE_H #include "cmark-gfm-core-extensions.h" extern cmark_node_type CMARK_NODE_TABLE, CMARK_NODE_TABLE_ROW, CMARK_NODE_TABLE_CELL; cmark_syntax_extension *create_table_extension(void); #endif �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/tagfilter.h�������������������������������������������������������������������0000644�0000000�0000000�00000000247�13442034251�015011� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_GFM_TAGFILTER_H #define CMARK_GFM_TAGFILTER_H #include "cmark-gfm-core-extensions.h" cmark_syntax_extension *create_tagfilter_extension(void); #endif ���������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/tasklist.h��������������������������������������������������������������������0000644�0000000�0000000�00000000220�13442037162�014661� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef TASKLIST_H #define TASKLIST_H #include "cmark-gfm-core-extensions.h" cmark_syntax_extension *create_tasklist_extension(void); #endif ��������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/cmark-gfm-extensions_export.h�������������������������������������������������0000644�0000000�0000000�00000002502�13442034251�020466� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������ #ifndef CMARK_GFM_EXTENSIONS_EXPORT_H #define CMARK_GFM_EXTENSIONS_EXPORT_H #ifdef CMARK_GFM_EXTENSIONS_STATIC_DEFINE # define CMARK_GFM_EXTENSIONS_EXPORT # define CMARK_GFM_EXTENSIONS_NO_EXPORT #else # ifndef CMARK_GFM_EXTENSIONS_EXPORT # ifdef libcmark_gfm_extensions_EXPORTS /* We are building this library */ # define CMARK_GFM_EXTENSIONS_EXPORT __attribute__((visibility("default"))) # else /* We are using this library */ # define CMARK_GFM_EXTENSIONS_EXPORT __attribute__((visibility("default"))) # endif # endif # ifndef CMARK_GFM_EXTENSIONS_NO_EXPORT # define CMARK_GFM_EXTENSIONS_NO_EXPORT __attribute__((visibility("hidden"))) # endif #endif #ifndef CMARK_GFM_EXTENSIONS_DEPRECATED # define CMARK_GFM_EXTENSIONS_DEPRECATED __attribute__ ((__deprecated__)) #endif #ifndef CMARK_GFM_EXTENSIONS_DEPRECATED_EXPORT # define CMARK_GFM_EXTENSIONS_DEPRECATED_EXPORT CMARK_GFM_EXTENSIONS_EXPORT CMARK_GFM_EXTENSIONS_DEPRECATED #endif #ifndef CMARK_GFM_EXTENSIONS_DEPRECATED_NO_EXPORT # define CMARK_GFM_EXTENSIONS_DEPRECATED_NO_EXPORT CMARK_GFM_EXTENSIONS_NO_EXPORT CMARK_GFM_EXTENSIONS_DEPRECATED #endif #if 0 /* DEFINE_NO_DEPRECATED */ # ifndef CMARK_GFM_EXTENSIONS_NO_DEPRECATED # define CMARK_GFM_EXTENSIONS_NO_DEPRECATED # endif #endif #endif /* CMARK_GFM_EXTENSIONS_EXPORT_H */ ����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/map.h�������������������������������������������������������������������������0000644�0000000�0000000�00000001471�13442034251�013605� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_MAP_H #define CMARK_MAP_H #include "memory.h" #include "chunk.h" #ifdef __cplusplus extern "C" { #endif struct cmark_map_entry { struct cmark_map_entry *next; unsigned char *label; unsigned int age; }; typedef struct cmark_map_entry cmark_map_entry; struct cmark_map; typedef void (*cmark_map_free_f)(struct cmark_map *, cmark_map_entry *); struct cmark_map { cmark_mem *mem; cmark_map_entry *refs; cmark_map_entry **sorted; unsigned int size; cmark_map_free_f free; }; typedef struct cmark_map cmark_map; unsigned char *normalize_map_label(cmark_mem *mem, cmark_chunk *ref); cmark_map *cmark_map_new(cmark_mem *mem, cmark_map_free_f free); void cmark_map_free(cmark_map *map); cmark_map_entry *cmark_map_lookup(cmark_map *map, cmark_chunk *label); #ifdef __cplusplus } #endif #endif �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/cbits/footnotes.h�������������������������������������������������������������������0000644�0000000�0000000�00000000620�13442034251�015043� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������#ifndef CMARK_FOOTNOTES_H #define CMARK_FOOTNOTES_H #include "map.h" #ifdef __cplusplus extern "C" { #endif struct cmark_footnote { cmark_map_entry entry; cmark_node *node; unsigned int ix; }; typedef struct cmark_footnote cmark_footnote; void cmark_footnote_create(cmark_map *map, cmark_node *node); cmark_map *cmark_footnote_map_new(cmark_mem *mem); #ifdef __cplusplus } #endif #endif ����������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/bench/sample.md���������������������������������������������������������������������0000644�0000000�0000000�00000024234�13315273412�014442� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������CommonMark ========== CommonMark is a rationalized version of Markdown syntax, with a [spec][the spec] and BSD3-licensed reference implementations in C and JavaScript. [Try it now!](http://spec.commonmark.org/dingus.html) The implementations ------------------- The C implementation provides both a shared library (`libcmark`) and a standalone program `cmark` that converts CommonMark to HTML. It is written in standard C99 and has no library dependencies. The parser is very fast (see [benchmarks](benchmarks.md)). It is easy to use `libcmark` in python, lua, ruby, and other dynamic languages: see the `wrappers/` subdirectory for some simple examples. The JavaScript implementation provides both an NPM package and a single JavaScript file, with no dependencies, that can be linked into an HTML page. For further information, see the [README in the js directory](js/README.md). **A note on security:** Neither implementation attempts to sanitize link attributes or raw HTML. If you use these libraries in applications that accept untrusted user input, you must run the output through an HTML sanitizer to protect against [XSS attacks](http://en.wikipedia.org/wiki/Cross-site_scripting). Installing (C) -------------- Building the C program (`cmark`) and shared library (`libcmark`) requires [cmake]. If you modify `scanners.re`, then you will also need [re2c], which is used to generate `scanners.c` from `scanners.re`. We have included a pre-generated `scanners.c` in the repository to reduce build dependencies. If you have GNU make, you can simply `make`, `make test`, and `make install`. This calls [cmake] to create a `Makefile` in the `build` directory, then uses that `Makefile` to create the executable and library. The binaries can be found in `build/src`. For a more portable method, you can use [cmake] manually. [cmake] knows how to create build environments for many build systems. For example, on FreeBSD: mkdir build cd build cmake .. # optionally: -DCMAKE_INSTALL_PREFIX=path make # executable will be created as build/src/cmark make test make install Or, to create Xcode project files on OSX: mkdir build cd build cmake -G Xcode .. make make test make install The GNU Makefile also provides a few other targets for developers. To run a benchmark: make bench To run a "fuzz test" against ten long randomly generated inputs: make fuzztest To run a test for memory leaks using `valgrind`: make leakcheck To reformat source code using `astyle`: make astyle To make a release tarball and zip archive: make archive Compiling for Windows --------------------- To compile with MSVC and NMAKE: nmake You can cross-compile a Windows binary and dll on linux if you have the `mingw32` compiler: make mingw The binaries will be in `build-mingw/windows/bin`. Installing (JavaScript) ----------------------- The JavaScript library can be installed through `npm`: npm install commonmark This includes a command-line converter called `commonmark`. If you want to use it in a client application, you can fetch a pre-built copy of `commonmark.js` from <http://spec.commonmark.org/js/commonmark.js>. For further information, see the [README in the js directory](js/README.md). The spec -------- [The spec] contains over 500 embedded examples which serve as conformance tests. To run the tests using an executable `$PROG`: python3 test/spec_tests.py --program $PROG If you want to extract the raw test data from the spec without actually running the tests, you can do: python3 test/spec_tests.py --dump-tests and you'll get all the tests in JSON format. [The spec]: http://spec.commonmark.org/0.13/ The source of [the spec] is `spec.txt`. This is basically a Markdown file, with code examples written in a shorthand form: . Markdown source . expected HTML output . To build an HTML version of the spec, do `make spec.html`. To build a PDF version, do `make spec.pdf`. (Creating a PDF requires [pandoc] and a LaTeX installation. Creating the HTML version requires only `libcmark` and `python3`.) The spec is written from the point of view of the human writer, not the computer reader. It is not an algorithm---an English translation of a computer program---but a declarative description of what counts as a block quote, a code block, and each of the other structural elements that can make up a Markdown document. Because John Gruber's [canonical syntax description](http://daringfireball.net/projects/markdown/syntax) leaves many aspects of the syntax undetermined, writing a precise spec requires making a large number of decisions, many of them somewhat arbitrary. In making them, we have appealed to existing conventions and considerations of simplicity, readability, expressive power, and consistency. We have tried to ensure that "normal" documents in the many incompatible existing implementations of Markdown will render, as far as possible, as their authors intended. And we have tried to make the rules for different elements work together harmoniously. In places where different decisions could have been made (for example, the rules governing list indentation), we have explained the rationale for my choices. In a few cases, we have departed slightly from the canonical syntax description, in ways that we think further the goals of Markdown as stated in that description. For the most part, we have limited ourselves to the basic elements described in Gruber's canonical syntax description, eschewing extensions like footnotes and definition lists. It is important to get the core right before considering such things. However, we have included a visible syntax for line breaks and fenced code blocks. Differences from original Markdown ---------------------------------- There are only a few places where this spec says things that contradict the canonical syntax description: - It allows all punctuation symbols to be backslash-escaped, not just the symbols with special meanings in Markdown. We found that it was just too hard to remember which symbols could be escaped. - It introduces an alternative syntax for hard line breaks, a backslash at the end of the line, supplementing the two-spaces-at-the-end-of-line rule. This is motivated by persistent complaints about the “invisible” nature of the two-space rule. - Link syntax has been made a bit more predictable (in a backwards-compatible way). For example, `Markdown.pl` allows single quotes around a title in inline links, but not in reference links. This kind of difference is really hard for users to remember, so the spec allows single quotes in both contexts. - The rule for HTML blocks differs, though in most real cases it shouldn't make a difference. (See the section on HTML Blocks for details.) The spec's proposal makes it easy to include Markdown inside HTML block-level tags, if you want to, but also allows you to exclude this. It is also makes parsing much easier, avoiding expensive backtracking. - It does not collapse adjacent bird-track blocks into a single blockquote: > this is two > blockquotes > this is a single > > blockquote with two paragraphs - Rules for content in lists differ in a few respects, though (as with HTML blocks), most lists in existing documents should render as intended. There is some discussion of the choice points and differences in the subsection of List Items entitled Motivation. We think that the spec's proposal does better than any existing implementation in rendering lists the way a human writer or reader would intuitively understand them. (We could give numerous examples of perfectly natural looking lists that nearly every existing implementation flubs up.) - The spec stipulates that two blank lines break out of all list contexts. This is an attempt to deal with issues that often come up when someone wants to have two adjacent lists, or a list followed by an indented code block. - Changing bullet characters, or changing from bullets to numbers or vice versa, starts a new list. We think that is almost always going to be the writer's intent. - The number that begins an ordered list item may be followed by either `.` or `)`. Changing the delimiter style starts a new list. - The start number of an ordered list is significant. - Fenced code blocks are supported, delimited by either backticks (```` ``` ```` or tildes (` ~~~ `). Contributing ------------ There is a [forum for discussing CommonMark](http://talk.commonmark.org); you should use it instead of github issues for questions and possibly open-ended discussions. Use the [github issue tracker](http://github.com/jgm/CommonMark/issues) only for simple, clear, actionable issues. Authors ------- The spec was written by John MacFarlane, drawing on - his experience writing and maintaining Markdown implementations in several languages, including the first Markdown parser not based on regular expression substitutions ([pandoc](http://github.com/jgm/pandoc)) and the first markdown parsers based on PEG grammars ([peg-markdown](http://github.com/jgm/peg-markdown), [lunamark](http://github.com/jgm/lunamark)) - a detailed examination of the differences between existing Markdown implementations using [BabelMark 2](http://johnmacfarlane.net/babelmark2/), and - extensive discussions with David Greenspan, Jeff Atwood, Vicent Marti, Neil Williams, and Benjamin Dumke-von der Ehe. John MacFarlane was also responsible for the original versions of the C and JavaScript implementations. The block parsing algorithm was worked out together with David Greenspan. Vicent Marti optimized the C implementation for performance, increasing its speed tenfold. Kārlis Gaņģis helped work out a better parsing algorithm for links and emphasis, eliminating several worst-case performance issues. Nick Wellnhofer contributed many improvements, including most of the C library's API and its test harness. Vitaly Puzrin has offered much good advice about the JavaScript implementation. [cmake]: http://www.cmake.org/download/ [pandoc]: http://johnmacfarlane.net/pandoc/ [re2c]: http://re2c.org ��������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������cmark-gfm-0.1.8/bench/full-sample.md����������������������������������������������������������������0000644�0000000�0000000�00000050462�13315273412�015404� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������CommonMark ========== CommonMark is a rationalized version of Markdown syntax, with a [spec][the spec] and BSD3-licensed reference implementations in C and JavaScript. [Try it now!](http://spec.commonmark.org/dingus.html) The implementations ------------------- The C implementation provides both a shared library (`libcmark`) and a standalone program `cmark` that converts CommonMark to HTML. It is written in standard C99 and has no library dependencies. The parser is very fast (see [benchmarks](benchmarks.md)). It is easy to use `libcmark` in python, lua, ruby, and other dynamic languages: see the `wrappers/` subdirectory for some simple examples. The JavaScript implementation provides both an NPM package and a single JavaScript file, with no dependencies, that can be linked into an HTML page. For further information, see the [README in the js directory](js/README.md). **A note on security:** Neither implementation attempts to sanitize link attributes or raw HTML. If you use these libraries in applications that accept untrusted user input, you must run the output through an HTML sanitizer to protect against [XSS attacks](http://en.wikipedia.org/wiki/Cross-site_scripting). Installing (C) -------------- Building the C program (`cmark`) and shared library (`libcmark`) requires [cmake]. If you modify `scanners.re`, then you will also need [re2c], which is used to generate `scanners.c` from `scanners.re`. We have included a pre-generated `scanners.c` in the repository to reduce build dependencies. If you have GNU make, you can simply `make`, `make test`, and `make install`. This calls [cmake] to create a `Makefile` in the `build` directory, then uses that `Makefile` to create the executable and library. The binaries can be found in `build/src`. For a more portable method, you can use [cmake] manually. [cmake] knows how to create build environments for many build systems. For example, on FreeBSD: mkdir build cd build cmake .. # optionally: -DCMAKE_INSTALL_PREFIX=path make # executable will be created as build/src/cmark make test make install Or, to create Xcode project files on OSX: mkdir build cd build cmake -G Xcode .. make make test make install The GNU Makefile also provides a few other targets for developers. To run a benchmark: make bench To run a "fuzz test" against ten long randomly generated inputs: make fuzztest To run a test for memory leaks using `valgrind`: make leakcheck To reformat source code using `astyle`: make astyle To make a release tarball and zip archive: make archive Compiling for Windows --------------------- To compile with MSVC and NMAKE: nmake You can cross-compile a Windows binary and dll on linux if you have the `mingw32` compiler: make mingw The binaries will be in `build-mingw/windows/bin`. Installing (JavaScript) ----------------------- The JavaScript library can be installed through `npm`: npm install commonmark This includes a command-line converter called `commonmark`. If you want to use it in a client application, you can fetch a pre-built copy of `commonmark.js` from <http://spec.commonmark.org/js/commonmark.js>. For further information, see the [README in the js directory](js/README.md). The spec -------- [The spec] contains over 500 embedded examples which serve as conformance tests. To run the tests using an executable `$PROG`: python3 test/spec_tests.py --program $PROG If you want to extract the raw test data from the spec without actually running the tests, you can do: python3 test/spec_tests.py --dump-tests and you'll get all the tests in JSON format. [The spec]: http://spec.commonmark.org/0.13/ The source of [the spec] is `spec.txt`. This is basically a Markdown file, with code examples written in a shorthand form: . Markdown source . expected HTML output . To build an HTML version of the spec, do `make spec.html`. To build a PDF version, do `make spec.pdf`. (Creating a PDF requires [pandoc] and a LaTeX installation. Creating the HTML version requires only `libcmark` and `python3`.) The spec is written from the point of view of the human writer, not the computer reader. It is not an algorithm---an English translation of a computer program---but a declarative description of what counts as a block quote, a code block, and each of the other structural elements that can make up a Markdown document. Because John Gruber's [canonical syntax description](http://daringfireball.net/projects/markdown/syntax) leaves many aspects of the syntax undetermined, writing a precise spec requires making a large number of decisions, many of them somewhat arbitrary. In making them, we have appealed to existing conventions and considerations of simplicity, readability, expressive power, and consistency. We have tried to ensure that "normal" documents in the many incompatible existing implementations of Markdown will render, as far as possible, as their authors intended. And we have tried to make the rules for different elements work together harmoniously. In places where different decisions could have been made (for example, the rules governing list indentation), we have explained the rationale for my choices. In a few cases, we have departed slightly from the canonical syntax description, in ways that we think further the goals of Markdown as stated in that description. For the most part, we have limited ourselves to the basic elements described in Gruber's canonical syntax description, eschewing extensions like footnotes and definition lists. It is important to get the core right before considering such things. However, we have included a visible syntax for line breaks and fenced code blocks. Differences from original Markdown ---------------------------------- There are only a few places where this spec says things that contradict the canonical syntax description: - It allows all punctuation symbols to be backslash-escaped, not just the symbols with special meanings in Markdown. We found that it was just too hard to remember which symbols could be escaped. - It introduces an alternative syntax for hard line breaks, a backslash at the end of the line, supplementing the two-spaces-at-the-end-of-line rule. This is motivated by persistent complaints about the “invisible” nature of the two-space rule. - Link syntax has been made a bit more predictable (in a backwards-compatible way). For example, `Markdown.pl` allows single quotes around a title in inline links, but not in reference links. This kind of difference is really hard for users to remember, so the spec allows single quotes in both contexts. - The rule for HTML blocks differs, though in most real cases it shouldn't make a difference. (See the section on HTML Blocks for details.) The spec's proposal makes it easy to include Markdown inside HTML block-level tags, if you want to, but also allows you to exclude this. It is also makes parsing much easier, avoiding expensive backtracking. - It does not collapse adjacent bird-track blocks into a single blockquote: > this is two > blockquotes > this is a single > > blockquote with two paragraphs - Rules for content in lists differ in a few respects, though (as with HTML blocks), most lists in existing documents should render as intended. There is some discussion of the choice points and differences in the subsection of List Items entitled Motivation. We think that the spec's proposal does better than any existing implementation in rendering lists the way a human writer or reader would intuitively understand them. (We could give numerous examples of perfectly natural looking lists that nearly every existing implementation flubs up.) - The spec stipulates that two blank lines break out of all list contexts. This is an attempt to deal with issues that often come up when someone wants to have two adjacent lists, or a list followed by an indented code block. - Changing bullet characters, or changing from bullets to numbers or vice versa, starts a new list. We think that is almost always going to be the writer's intent. - The number that begins an ordered list item may be followed by either `.` or `)`. Changing the delimiter style starts a new list. - The start number of an ordered list is significant. - Fenced code blocks are supported, delimited by either backticks (```` ``` ```` or tildes (` ~~~ `). Contributing ------------ There is a [forum for discussing CommonMark](http://talk.commonmark.org); you should use it instead of github issues for questions and possibly open-ended discussions. Use the [github issue tracker](http://github.com/jgm/CommonMark/issues) only for simple, clear, actionable issues. Authors ------- The spec was written by John MacFarlane, drawing on - his experience writing and maintaining Markdown implementations in several languages, including the first Markdown parser not based on regular expression substitutions ([pandoc](http://github.com/jgm/pandoc)) and the first markdown parsers based on PEG grammars ([peg-markdown](http://github.com/jgm/peg-markdown), [lunamark](http://github.com/jgm/lunamark)) - a detailed examination of the differences between existing Markdown implementations using [BabelMark 2](http://johnmacfarlane.net/babelmark2/), and - extensive discussions with David Greenspan, Jeff Atwood, Vicent Marti, Neil Williams, and Benjamin Dumke-von der Ehe. John MacFarlane was also responsible for the original versions of the C and JavaScript implementations. The block parsing algorithm was worked out together with David Greenspan. Vicent Marti optimized the C implementation for performance, increasing its speed tenfold. Kārlis Gaņģis helped work out a better parsing algorithm for links and emphasis, eliminating several worst-case performance issues. Nick Wellnhofer contributed many improvements, including most of the C library's API and its test harness. Vitaly Puzrin has offered much good advice about the JavaScript implementation. [cmake]: http://www.cmake.org/download/ [pandoc]: http://johnmacfarlane.net/pandoc/ [re2c]: http://re2c.org > the simple example of a blockquote > the simple example of a blockquote > the simple example of a blockquote > the simple example of a blockquote ... continuation ... continuation ... continuation ... continuation empty blockquote: > > > > >>>>>> deeply nested blockquote >>>>> deeply nested blockquote >>>> deeply nested blockquote >>> deeply nested blockquote >> deeply nested blockquote > deeply nested blockquote > deeply nested blockquote >> deeply nested blockquote >>> deeply nested blockquote >>>> deeply nested blockquote >>>>> deeply nested blockquote >>>>>> deeply nested blockquote an example of a code block ``````````text an example ``` of a fenced ``` code block `````````` # heading ### heading ##### heading # heading # ### heading ### ##### heading \#\#\#\#\###### ############ not a heading * * * * * - - - - - ________ ************************* text <div class="this is an html block"> blah blah </div> <table> <tr> <td> **test** </td> </tr> </table> <table> <tr> <td> test </td> </tr> </table> <![CDATA[ [[[[[[[[[[[... *cdata section - this should not be parsed* ...]]]]]]]]]]] ]]> heading --- heading =================================== not a heading ----------------------------------- text - tidy - bullet - list - loose - bullet - list 0. ordered 1. list 2. example - - - - 1. 2. 3. - an example of a list item with a continuation this part is inside the list this part is just a paragraph 1. test - test 1. test - test 111111111111111111111111111111111111111111. is this a valid bullet? - _________________________ - this - is a long - loose - list - with - some tidy - list - items - in - between - _________________________ - this - is - a - deeply - nested - bullet - list 1. this 2. is 3. a 4. deeply 5. nested 6. unordered 7. list - 1 - 2 - 3 - 4 - 5 - 6 - 7 - 6 - 5 - 4 - 3 - 2 - 1 - - - - - - - - - deeply-nested one-element item [1] [2] [3] [1] [2] [3] [looooooooooooooooooooooooooooooooooooooooooooooooooong label] [1]: <http://something.example.com/foo/bar> [2]: http://something.example.com/foo/bar 'test' [3]: http://foo/bar [ looooooooooooooooooooooooooooooooooooooooooooooooooong label ]: 111 'test' [[[[[[[[[[[[[[[[[[[[ this should not slow down anything ]]]]]]]]]]]]]]]]]]]]: q (as long as it is not referenced anywhere) [[[[[[[[[[[[[[[[[[[[]: this is not a valid reference [[[[[[[foo]]]]]]] [[[[[[[foo]]]]]]]: bar [[[[[[foo]]]]]]: bar [[[[[foo]]]]]: bar [[[[foo]]]]: bar [[[foo]]]: bar [[foo]]: bar [foo]: bar [*[*[*[*[foo]*]*]*]*] [*[*[*[*[foo]*]*]*]*]: bar [*[*[*[foo]*]*]*]: bar [*[*[foo]*]*]: bar [*[foo]*]: bar [foo]: bar closed (valid) autolinks: <ftp://1.2.3.4:21/path/foo> <http://foo.bar.baz?q=hello&id=22&boolean> <http://veeeeeeeeeeeeeeeeeeery.loooooooooooooooooooooooooooooooong.autolink/> <teeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeest@gmail.com> these are not autolinks: <ftp://1.2.3.4:21/path/foo <http://foo.bar.baz?q=hello&id=22&boolean <http://veeeeeeeeeeeeeeeeeeery.loooooooooooooooooooooooooooooooong.autolink <teeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeeest@gmail.com < http://foo.bar.baz?q=hello&id=22&boolean > `lots`of`backticks` ``i``wonder``how``this``will``be``parsed`` *this* *is* *your* *basic* *boring* *emphasis* _this_ _is_ _your_ _basic_ _boring_ _emphasis_ **this** **is** **your** **basic** **boring** **emphasis** *this *is *a *bunch* of* nested* emphases* __this __is __a __bunch__ of__ nested__ emphases__ ***this ***is ***a ***bunch*** of*** nested*** emphases*** *this *is *a *worst *case *for *em *backtracking __this __is __a __worst __case __for __em __backtracking ***this ***is ***a ***worst ***case ***for ***em ***backtracking entities: &nbsp; &amp; &copy; &AElig; &Dcaron; &frac34; &HilbertSpace; &DifferentialD; &ClockwiseContourIntegral; &#35; &#1234; &#992; &#98765432; non-entities: &18900987654321234567890; &1234567890098765432123456789009876543212345678987654; &qwertyuioppoiuytrewqwer; &oiuytrewqwertyuioiuytrewqwertyuioytrewqwertyuiiuytri; \t\e\s\t\i\n\g \e\s\c\a\p\e \s\e\q\u\e\n\c\e\s \!\\\"\#\$\%\&\'\(\)\*\+\,\.\/\:\;\<\=\>\? \@ \[ \] \^ \_ \` \{ \| \} \~ \- \' \ \\ \\\ \\\\ \\\\\ \<this\> \<is\> \<not\> \<html\> Taking commonmark tests from the spec for benchmarking here: <a><bab><c2c> <a/><b2/> <a /><b2 data="foo" > <a foo="bar" bam = 'baz <em>"</em>' _boolean zoop:33=zoop:33 /> <33> <__> <a h*#ref="hi"> <a href="hi'> <a href=hi'> < a>< foo><bar/ > <a href='bar'title=title> </a> </foo > </a href="foo"> foo <!-- this is a comment - with hyphen --> foo <!-- not a comment -- two hyphens --> foo <?php echo $a; ?> foo <!ELEMENT br EMPTY> foo <![CDATA[>&<]]> <a href="&ouml;"> <a href="\*"> <a href="\""> Valid links: [this is a link]() [this is a link](<http://something.example.com/foo/bar>) [this is a link](http://something.example.com/foo/bar 'test') ![this is an image]() ![this is an image](<http://something.example.com/foo/bar>) ![this is an image](http://something.example.com/foo/bar 'test') [escape test](<\>\>\>\>\>\>\>\>\>\>\>\>\>\>> '\'\'\'\'\'\'\'\'\'\'\'\'\'\'') [escape test \]\]\]\]\]\]\]\]\]\]\]\]\]\]\]\]](\)\)\)\)\)\)\)\)\)\)\)\)\)\)) Invalid links: [this is not a link [this is not a link]( [this is not a link](http://something.example.com/foo/bar 'test' [this is not a link]((((((((((((((((((((((((((((((((((((((((((((((( [this is not a link]((((((((((()))))))))) (((((((((())))))))))) Valid links: [[[[[[[[](test)](test)](test)](test)](test)](test)](test)] [ [[[[[[[[[[[[[[[[[[ [](test) ]]]]]]]]]]]]]]]]]] ](test) Invalid links: [[[[[[[[[ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ [ ![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![![ this\ should\ be\ separated\ by\ newlines this should be separated by newlines too this should not be separated by newlines Lorem ipsum dolor sit amet, __consectetur__ adipiscing elit. Cras imperdiet nec erat ac condimentum. Nulla vel rutrum ligula. Sed hendrerit interdum orci a posuere. Vivamus ut velit aliquet, mollis purus eget, iaculis nisl. Proin posuere malesuada ante. Proin auctor orci eros, ac molestie lorem dictum nec. Vestibulum sit amet erat est. Morbi luctus sed elit ac luctus. Proin blandit, enim vitae egestas posuere, neque elit ultricies dui, vel mattis nibh enim ac lorem. Maecenas molestie nisl sit amet velit dictum lobortis. Aliquam erat volutpat. Vivamus sagittis, diam in [vehicula](https://github.com/markdown-it/markdown-it) lobortis, sapien arcu mattis erat, vel aliquet sem urna et risus. Ut feugiat sapien vitae mi elementum laoreet. Suspendisse potenti. Aliquam erat nisl, aliquam pretium libero aliquet, sagittis eleifend nunc. In hac habitasse platea dictumst. Integer turpis augue, tincidunt dignissim mauris id, rhoncus dapibus purus. Maecenas et enim odio. Nullam massa metus, varius quis vehicula sed, pharetra mollis erat. In quis viverra velit. Vivamus placerat, est nec hendrerit varius, enim dui hendrerit magna, ut pulvinar nibh lorem vel lacus. Mauris a orci iaculis, hendrerit eros sed, gravida leo. In dictum mauris vel augue varius, ac ullamcorper nisl ornare. In eu posuere velit, ac fermentum arcu. Interdum et malesuada fames ac ante ipsum primis in faucibus. Nullam sed malesuada leo, at interdum elit. Nullam ut tincidunt nunc. [Pellentesque][1] metus lacus, commodo eget justo ut, rutrum varius nunc. Sed non rhoncus risus. Morbi sodales gravida pulvinar. Duis malesuada, odio volutpat elementum vulputate, massa magna scelerisque ante, et accumsan tellus nunc in sem. Donec mattis arcu et velit aliquet, non sagittis justo vestibulum. Suspendisse volutpat felis lectus, nec consequat ipsum mattis id. Donec dapibus vehicula facilisis. In tincidunt mi nisi, nec faucibus tortor euismod nec. Suspendisse ante ligula, aliquet vitae libero eu, vulputate dapibus libero. Sed bibendum, sapien at posuere interdum, libero est sollicitudin magna, ac gravida tellus purus eu ipsum. Proin ut quam arcu. Suspendisse potenti. Donec ante velit, ornare at augue quis, tristique laoreet sem. Etiam in ipsum elit. Nullam cursus dolor sit amet nulla feugiat tristique. Phasellus ac tellus tincidunt, imperdiet purus eget, ullamcorper ipsum. Cras eu tincidunt sem. Nullam sed dapibus magna. Lorem ipsum dolor sit amet, consectetur adipiscing elit. In id venenatis tortor. In consectetur sollicitudin pharetra. Etiam convallis nisi nunc, et aliquam turpis viverra sit amet. Maecenas faucibus sodales tortor. Suspendisse lobortis mi eu leo viverra volutpat. Pellentesque velit ante, vehicula sodales congue ut, elementum a urna. Cras tempor, ipsum eget luctus rhoncus, arcu ligula fermentum urna, vulputate pharetra enim enim non libero. Proin diam quam, elementum in eleifend id, elementum et metus. Cras in justo consequat justo semper ultrices. Sed dignissim lectus a ante mollis, nec vulputate ante molestie. Proin in porta nunc. Etiam pulvinar turpis sed velit porttitor, vel adipiscing velit fringilla. Cras ac tellus vitae purus pharetra tincidunt. Sed cursus aliquet aliquet. Cras eleifend commodo malesuada. In turpis turpis, ullamcorper ut tincidunt a, ullamcorper a nunc. Etiam luctus tellus ac dapibus gravida. Ut nec lacus laoreet neque ullamcorper volutpat. Nunc et leo erat. Aenean mattis ultrices lorem, eget adipiscing dolor ultricies eu. In hac habitasse platea dictumst. Vivamus cursus feugiat sapien quis aliquam. Mauris quam libero, porta vel volutpat ut, blandit a purus. Vivamus vestibulum dui vel tortor molestie, sit amet feugiat sem commodo. Nulla facilisi. Sed molestie arcu eget tellus vestibulum tristique. [1]: https://github.com/markdown-it this is a test for tab expansion, be careful not to replace them with spaces 1 4444 22 333 333 22 4444 1 tab-indented line space-indented line tab-indented line a lot of spaces in between here a lot of tabs in between here ������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������