diff options
Diffstat (limited to 'src')
| -rw-r--r-- | src/Text/Pandoc/App/CommandLineOptions.hs | 4 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Shared.hs | 3 | ||||
| -rw-r--r-- | src/Text/Pandoc/Shared.hs | 11 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/LaTeX/Util.hs | 6 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Org.hs | 4 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 8 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Textile.hs | 14 |
10 files changed, 22 insertions, 34 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs index 2acfba75f..fda83d7c6 100644 --- a/src/Text/Pandoc/App/CommandLineOptions.hs +++ b/src/Text/Pandoc/App/CommandLineOptions.hs @@ -50,7 +50,7 @@ import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), IpynbOutput (..), fullDefaultsPath) import Text.Pandoc.Filter (Filter (..)) import Text.Pandoc.Highlighting (highlightingStyles, lookupHighlightingStyle) -import Text.Pandoc.Shared (ordNub, elemText, safeStrRead, defaultUserDataDir) +import Text.Pandoc.Shared (ordNub, safeStrRead, defaultUserDataDir) import Text.Printf import qualified Control.Exception as E import qualified Data.ByteString as BS @@ -1006,7 +1006,7 @@ writersNames = sort ("pdf" : map fst (writers :: [(Text, Writer PandocIO)])) splitField :: String -> (String, String) -splitField = second (tailDef "true") . break (`elemText` ":=") +splitField = second (tailDef "true") . break (\c -> c == ':' || c == '=') deprecatedOption :: String -> String -> IO () deprecatedOption o msg = diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 58bf2becf..530fe8f2a 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -315,7 +315,7 @@ tok = tokWith inline unescapeURL :: Text -> Text unescapeURL = T.concat . go . T.splitOn "\\" where - isEscapable c = c `elemText` "#$%&~_^\\{}" + isEscapable c = T.any (== c) "#$%&~_^\\{}" go (x:xs) = x : map unescapeInterior xs go [] = [] unescapeInterior t diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index f41644116..7e31db093 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -23,7 +23,6 @@ import qualified Data.Text as T import System.FilePath (isValid, takeExtension) import qualified System.FilePath.Posix as Posix import qualified System.FilePath.Windows as Windows -import Text.Pandoc.Shared (elemText) -- | Check whether the given string looks like the path to of URL of an image. isImageFilename :: Text -> Bool @@ -58,7 +57,7 @@ cleanLinkText s isUrl :: Text -> Bool isUrl cs = let (scheme, path) = T.break (== ':') cs - in T.all (\c -> isAlphaNum c || c `elemText` ".-") scheme + in T.all (\c -> isAlphaNum c || T.any (== c) ".-") scheme && not (T.null path) -- | Creates an key-value pair marking the original language name specified for diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index b2d14c52a..34b67f0b7 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -27,8 +27,6 @@ module Text.Pandoc.Shared ( -- * Text processing inquotes, tshow, - elemText, - notElemText, stripTrailingNewlines, trim, triml, @@ -191,15 +189,6 @@ inquotes txt = T.cons '\"' (T.snoc txt '\"') tshow :: Show a => a -> T.Text tshow = T.pack . show --- | @True@ exactly when the @Char@ appears in the @Text@. -elemText :: Char -> T.Text -> Bool -elemText c = T.any (== c) - -{-# DEPRECATED notElemText "Use T.all (/= c)" #-} --- | @True@ exactly when the @Char@ does not appear in the @Text@. -notElemText :: Char -> T.Text -> Bool -notElemText c = T.all (/= c) - -- | Strip trailing newlines from string. stripTrailingNewlines :: T.Text -> T.Text stripTrailingNewlines = T.dropWhileEnd (== '\n') diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 56f68f2c8..9e909bed6 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -538,7 +538,7 @@ inlineToConTeXt (Subscript lst) = do inlineToConTeXt (SmallCaps lst) = do contents <- inlineListToConTeXt lst return $ braces $ "\\sc " <> contents -inlineToConTeXt (Code _ str) | not ('{' `elemText` str || '}' `elemText` str) = +inlineToConTeXt (Code _ str) | not (T.any (\c -> c == '{' || c == '}') str) = return $ "\\type" <> braces (literal str) inlineToConTeXt (Code _ str) = do opts <- gets stOptions diff --git a/src/Text/Pandoc/Writers/LaTeX/Util.hs b/src/Text/Pandoc/Writers/LaTeX/Util.hs index 9ff46f587..1db4983a1 100644 --- a/src/Text/Pandoc/Writers/LaTeX/Util.hs +++ b/src/Text/Pandoc/Writers/LaTeX/Util.hs @@ -37,7 +37,7 @@ import qualified Data.Text as T import Text.Pandoc.Extensions (Extension(Ext_smart)) import Data.Char (isLetter, isSpace, isDigit, isAscii, ord, isAlphaNum) import Text.Printf (printf) -import Text.Pandoc.Shared (safeRead, elemText) +import Text.Pandoc.Shared (safeRead) import qualified Data.Text.Normalize as Normalize import Data.List (uncons) @@ -50,7 +50,7 @@ data StringContext = TextString stringToLaTeX :: PandocMonad m => StringContext -> Text -> LW m Text stringToLaTeX context zs = do opts <- gets stOptions - when ('\x200c' `elemText` zs) $ + when (T.any (== '\x200c') zs) $ modify (\s -> s { stZwnj = True }) return $ T.pack $ foldr (go opts context) mempty $ T.unpack $ @@ -182,7 +182,7 @@ toLabel z = go `fmap` stringToLaTeX URLString z where go = T.concatMap $ \x -> case x of _ | (isLetter x || isDigit x) && isAscii x -> T.singleton x - | x `elemText` "_-+=:;." -> T.singleton x + | T.any (== x) "_-+=:;." -> T.singleton x | otherwise -> T.pack $ "ux" <> printf "%x" (ord x) -- | Puts contents into LaTeX command. diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index c6200f5b0..9b61a565a 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -398,7 +398,7 @@ blockToMarkdown' opts (Div attrs ils) = do blockToMarkdown' opts (Plain inlines) = do -- escape if para starts with ordered list marker variant <- asks envVariant - let escapeMarker = T.concatMap $ \x -> if x `elemText` ".()" + let escapeMarker = T.concatMap $ \x -> if T.any (== x) ".()" then T.pack ['\\', x] else T.singleton x let startsWithSpace (Space:_) = True diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 30d892365..24632109b 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -514,8 +514,8 @@ orgPath src = case T.uncons src of isUrl :: Text -> Bool isUrl cs = let (scheme, path) = T.break (== ':') cs - in T.all (\c -> isAlphaNum c || c `elemText` ".-") scheme - && not (T.null path) + in T.all (\c -> isAlphaNum c || T.any (== c) ".-") scheme + && not (T.null path) -- | Translate from pandoc's programming language identifiers to those used by -- org-mode. diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index c09835455..d783852cd 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -626,14 +626,14 @@ transformInlines = insertBS . okAfterComplex SoftBreak = True okAfterComplex LineBreak = True okAfterComplex (Str (T.uncons -> Just (c,_))) - = isSpace c || c `elemText` "-.,:;!?\\/'\")]}>–—" + = isSpace c || T.any (== c) "-.,:;!?\\/'\")]}>–—" okAfterComplex _ = False okBeforeComplex :: Inline -> Bool okBeforeComplex Space = True okBeforeComplex SoftBreak = True okBeforeComplex LineBreak = True okBeforeComplex (Str (T.unsnoc -> Just (_,c))) - = isSpace c || c `elemText` "-:/'\"<([{–—" + = isSpace c || T.any (== c) "-:/'\"<([{–—" okBeforeComplex _ = False isComplex :: Inline -> Bool isComplex (Emph _) = True @@ -791,7 +791,7 @@ inlineToRST (Code _ str) = do -- we use :literal: when the code contains backticks, since -- :literal: allows backslash-escapes; see #3974 return $ - if '`' `elemText` str + if T.any (== '`') str then ":literal:`" <> literal (escapeText opts (trim str)) <> "`" else "``" <> literal (trim str) <> "``" inlineToRST (Str str) = do @@ -804,7 +804,7 @@ inlineToRST (Math t str) = do modify $ \st -> st{ stHasMath = True } return $ if t == InlineMath then ":math:`" <> literal str <> "`" - else if '\n' `elemText` str + else if T.any (== '\n') str then blankline $$ ".. math::" $$ blankline $$ nest 3 (literal str) $$ blankline else blankline $$ (".. math:: " <> literal str) $$ blankline diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index f27a38b08..ee31ab378 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -380,37 +380,37 @@ inlineToTextile opts (Span _ lst) = inlineToTextile opts (Emph lst) = do contents <- inlineListToTextile opts lst - return $ if '_' `elemText` contents + return $ if T.any (== '_') contents then "<em>" <> contents <> "</em>" else "_" <> contents <> "_" inlineToTextile opts (Underline lst) = do contents <- inlineListToTextile opts lst - return $ if '+' `elemText` contents + return $ if T.any (== '+') contents then "<u>" <> contents <> "</u>" else "+" <> contents <> "+" inlineToTextile opts (Strong lst) = do contents <- inlineListToTextile opts lst - return $ if '*' `elemText` contents + return $ if T.any (== '*') contents then "<strong>" <> contents <> "</strong>" else "*" <> contents <> "*" inlineToTextile opts (Strikeout lst) = do contents <- inlineListToTextile opts lst - return $ if '-' `elemText` contents + return $ if T.any (== '-') contents then "<del>" <> contents <> "</del>" else "-" <> contents <> "-" inlineToTextile opts (Superscript lst) = do contents <- inlineListToTextile opts lst - return $ if '^' `elemText` contents + return $ if T.any (== '^') contents then "<sup>" <> contents <> "</sup>" else "[^" <> contents <> "^]" inlineToTextile opts (Subscript lst) = do contents <- inlineListToTextile opts lst - return $ if '~' `elemText` contents + return $ if T.any (== '~') contents then "<sub>" <> contents <> "</sub>" else "[~" <> contents <> "~]" @@ -427,7 +427,7 @@ inlineToTextile opts (Quoted DoubleQuote lst) = do inlineToTextile opts (Cite _ lst) = inlineListToTextile opts lst inlineToTextile _ (Code _ str) = - return $ if '@' `elemText` str + return $ if T.any (== '@') str then "<tt>" <> escapeStringForXML str <> "</tt>" else "@" <> str <> "@" |
