From 3f8d3d844fde31a27643254be69a17128a47d3fe Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Fri, 2 Sep 2016 11:35:28 -0400 Subject: Remove TagSoup compat We already lower-bound tagsoup at 0.13.7, which means we were always running the compatibility layer (it was conditional on min value 0.13). Better to just use `lookupEntity` from the library directly, and convert a string to a char if need be. --- src/Text/Pandoc/Compat/TagSoupEntity.hs | 15 --------------- src/Text/Pandoc/Parsing.hs | 6 +++--- src/Text/Pandoc/Readers/DocBook.hs | 6 +++--- src/Text/Pandoc/Readers/OPML.hs | 4 ++-- src/Text/Pandoc/XML.hs | 4 ++-- 5 files changed, 10 insertions(+), 25 deletions(-) delete mode 100644 src/Text/Pandoc/Compat/TagSoupEntity.hs (limited to 'src/Text') diff --git a/src/Text/Pandoc/Compat/TagSoupEntity.hs b/src/Text/Pandoc/Compat/TagSoupEntity.hs deleted file mode 100644 index 80985aef9..000000000 --- a/src/Text/Pandoc/Compat/TagSoupEntity.hs +++ /dev/null @@ -1,15 +0,0 @@ -{-# LANGUAGE CPP #-} -module Text.Pandoc.Compat.TagSoupEntity (lookupEntity - ) where - -import qualified Text.HTML.TagSoup.Entity as TE - -lookupEntity :: String -> Maybe Char -#if MIN_VERSION_tagsoup(0,13,0) -lookupEntity = str2chr . TE.lookupEntity - where str2chr :: Maybe String -> Maybe Char - str2chr (Just [c]) = Just c - str2chr _ = Nothing -#else -lookupEntity = TE.lookupEntity -#endif diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index b710f930d..e45e2247d 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -184,7 +184,7 @@ import Text.Pandoc.Shared import qualified Data.Map as M import Text.TeXMath.Readers.TeX.Macros (applyMacros, Macro, parseMacroDefinitions) -import Text.Pandoc.Compat.TagSoupEntity ( lookupEntity ) +import Text.HTML.TagSoup.Entity ( lookupEntity ) import Text.Pandoc.Asciify (toAsciiChar) import Data.Monoid ((<>)) import Data.Default @@ -578,8 +578,8 @@ characterReference = try $ do '#':_ -> ent _ -> ent ++ ";" case lookupEntity ent' of - Just c -> return c - Nothing -> fail "entity not found" + Just (c : _) -> return c + _ -> fail "entity not found" -- | Parses an uppercase roman numeral and returns (UpperRoman, number). upperRoman :: Stream s m Char => ParserT s st m (ListNumberStyle, Int) diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 9bd51f5a8..336b40933 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -5,7 +5,7 @@ import Text.Pandoc.Options import Text.Pandoc.Definition import Text.Pandoc.Builder import Text.XML.Light -import Text.Pandoc.Compat.TagSoupEntity (lookupEntity) +import Text.HTML.TagSoup.Entity (lookupEntity) import Data.Either (rights) import Data.Generics import Data.Char (isSpace) @@ -564,7 +564,7 @@ normalizeTree = everywhere (mkT go) go xs = xs convertEntity :: String -> String -convertEntity e = maybe (map toUpper e) (:[]) (lookupEntity e) +convertEntity e = maybe (map toUpper e) id (lookupEntity e) -- convenience function to get an attribute value, defaulting to "" attrValue :: String -> Element -> String @@ -916,7 +916,7 @@ elementToStr x = x parseInline :: Content -> DB Inlines parseInline (Text (CData _ s _)) = return $ text s parseInline (CRef ref) = - return $ maybe (text $ map toUpper ref) (text . (:[])) $ lookupEntity ref + return $ maybe (text $ map toUpper ref) (text) $ lookupEntity ref parseInline (Elem e) = case qName (elName e) of "equation" -> equation displayMath diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs index 7ee9ef398..4dcf5e5a0 100644 --- a/src/Text/Pandoc/Readers/OPML.hs +++ b/src/Text/Pandoc/Readers/OPML.hs @@ -7,7 +7,7 @@ import Text.Pandoc.Builder import Text.Pandoc.Readers.HTML (readHtml) import Text.Pandoc.Readers.Markdown (readMarkdown) import Text.XML.Light -import Text.Pandoc.Compat.TagSoupEntity (lookupEntity) +import Text.HTML.TagSoup.Entity (lookupEntity) import Data.Generics import Control.Monad.State import Data.Default @@ -53,7 +53,7 @@ normalizeTree = everywhere (mkT go) go xs = xs convertEntity :: String -> String -convertEntity e = maybe (map toUpper e) (:[]) (lookupEntity e) +convertEntity e = maybe (map toUpper e) id (lookupEntity e) -- convenience function to get an attribute value, defaulting to "" attrValue :: String -> Element -> String diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index 4cc2141b4..e105aee91 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -38,7 +38,7 @@ module Text.Pandoc.XML ( escapeCharForXML, import Text.Pandoc.Pretty import Data.Char (ord, isAscii, isSpace) -import Text.Pandoc.Compat.TagSoupEntity (lookupEntity) +import Text.HTML.TagSoup.Entity (lookupEntity) -- | Escape one character as needed for XML. escapeCharForXML :: Char -> String @@ -101,7 +101,7 @@ toEntities (c:cs) fromEntities :: String -> String fromEntities ('&':xs) = case lookupEntity ent' of - Just c -> c : fromEntities rest + Just c -> c ++ fromEntities rest Nothing -> '&' : fromEntities xs where (ent, rest) = case break (\c -> isSpace c || c == ';') xs of (zs,';':ys) -> (zs,ys) -- cgit v1.2.3