diff options
author | Vaibhav Sagar <vaibhavsagar@gmail.com> | 2020-04-28 22:53:06 +0800 |
---|---|---|
committer | GitHub <noreply@github.com> | 2020-04-28 07:53:06 -0700 |
commit | 9c2b659eeb196145f62d8eae0072c279a7c2d751 (patch) | |
tree | f3c97feb0f1d063e2a7c65904c9fbe1591104a05 /src/Text/Pandoc/Readers | |
parent | 8d09a92d979126a53ec72ec73294ad04f811e9a7 (diff) | |
download | pandoc-9c2b659eeb196145f62d8eae0072c279a7c2d751.tar.gz |
Support new Underline element in readers and writers (#6277)
Deprecate `underlineSpan` in Shared in favor of `Text.Pandoc.Builder.underline`.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/Docx.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/DokuWiki.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/JATS.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 15 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Muse.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/ContentReader.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Txt2Tags.hs | 5 |
11 files changed, 32 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index bb86c91b0..ddec0bdf8 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -299,7 +299,7 @@ runStyleToTransform rPr return $ subscript . transform | Just "single" <- rUnderline rPr = do transform <- runStyleToTransform rPr{rUnderline = Nothing} - return $ underlineSpan . transform + return $ Pandoc.underline . transform | otherwise = return id runToInlines :: PandocMonad m => Run -> DocxContext m Inlines diff --git a/src/Text/Pandoc/Readers/DokuWiki.hs b/src/Text/Pandoc/Readers/DokuWiki.hs index 8b48789b3..722701ee2 100644 --- a/src/Text/Pandoc/Readers/DokuWiki.hs +++ b/src/Text/Pandoc/Readers/DokuWiki.hs @@ -29,7 +29,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Error (PandocError (PandocParsecError)) import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (enclosed, nested) -import Text.Pandoc.Shared (crFilter, trim, underlineSpan, stringify, tshow) +import Text.Pandoc.Shared (crFilter, trim, stringify, tshow) -- | Read DokuWiki from an input string and return a Pandoc document. readDokuWiki :: PandocMonad m @@ -162,7 +162,7 @@ italic :: PandocMonad m => DWParser m B.Inlines italic = try $ B.emph <$> enclosed (string "//") nestedInlines underlined :: PandocMonad m => DWParser m B.Inlines -underlined = try $ underlineSpan <$> enclosed (string "__") nestedInlines +underlined = try $ B.underline <$> enclosed (string "__") nestedInlines nowiki :: PandocMonad m => DWParser m B.Inlines nowiki = try $ B.text <$ string "<nowiki>" <*> manyTillChar anyChar (try $ string "</nowiki>") diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 1ab35bf7a..a643ed41f 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -61,7 +61,7 @@ import Text.Pandoc.Options ( import Text.Pandoc.Parsing hiding ((<|>)) import Text.Pandoc.Shared (addMetaField, blocksToInlines', crFilter, escapeURI, extractSpaces, htmlSpanLikeElements, elemText, splitTextBy, - onlySimpleTableCells, safeRead, underlineSpan, tshow) + onlySimpleTableCells, safeRead, tshow) import Text.Pandoc.Walk import Text.Parsec.Error import Text.TeXMath (readMathML, writeTeX) @@ -749,7 +749,7 @@ pStrikeout = return $ B.strikeout contents) pUnderline :: PandocMonad m => TagParser m Inlines -pUnderline = pInlinesInTags "u" underlineSpan <|> pInlinesInTags "ins" underlineSpan +pUnderline = pInlinesInTags "u" B.underline <|> pInlinesInTags "ins" B.underline pLineBreak :: PandocMonad m => TagParser m Inlines pLineBreak = do diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs index f78630ec0..d7f87f695 100644 --- a/src/Text/Pandoc/Readers/JATS.hs +++ b/src/Text/Pandoc/Readers/JATS.hs @@ -26,7 +26,7 @@ import Text.HTML.TagSoup.Entity (lookupEntity) import Text.Pandoc.Builder import Text.Pandoc.Class.PandocMonad (PandocMonad) import Text.Pandoc.Options -import Text.Pandoc.Shared (underlineSpan, crFilter, safeRead) +import Text.Pandoc.Shared (crFilter, safeRead) import Text.TeXMath (readMathML, writeTeX) import Text.XML.Light import qualified Data.Set as S (fromList, member) @@ -456,7 +456,7 @@ parseInline (Elem e) = "strike" -> strikeout <$> innerInlines "sub" -> subscript <$> innerInlines "sup" -> superscript <$> innerInlines - "underline" -> underlineSpan <$> innerInlines + "underline" -> underline <$> innerInlines "break" -> return linebreak "sc" -> smallcaps <$> innerInlines diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index b6bc039df..245c4957f 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -909,7 +909,7 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList , ("slash", lit "/") , ("textbf", extractSpaces strong <$> tok) , ("textnormal", extractSpaces (spanWith ("",["nodecor"],[])) <$> tok) - , ("underline", underlineSpan <$> tok) + , ("underline", underline <$> tok) , ("ldots", lit "…") , ("vdots", lit "\8942") , ("dots", lit "…") @@ -1171,9 +1171,9 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList -- include , ("input", rawInlineOr "input" $ include "input") -- soul package - , ("ul", underlineSpan <$> tok) + , ("ul", underline <$> tok) -- ulem package - , ("uline", underlineSpan <$> tok) + , ("uline", underline <$> tok) -- plain tex stuff that should just be passed through as raw tex , ("ifdim", ifdim) ] diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 72a0975fd..3b363263d 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1751,7 +1751,9 @@ bracketedSpan = try $ do attr <- attributes return $ if isSmallCaps attr then B.smallcaps <$> lab - else B.spanWith attr <$> lab + else if isUnderline attr + then B.underline <$> lab + else B.spanWith attr <$> lab -- | We treat a span as SmallCaps if class is "smallcaps" (and -- no other attributes are set or if style is "font-variant:small-caps" @@ -1765,6 +1767,13 @@ isSmallCaps ("",[],kvs) = Nothing -> False isSmallCaps _ = False +-- | We treat a span as Underline if class is "ul" or +-- "underline" (and no other attributes are set). +isUnderline :: Attr -> Bool +isUnderline ("",["ul"],[]) = True +isUnderline ("",["underline"],[]) = True +isUnderline _ = False + regLink :: PandocMonad m => (Attr -> Text -> Text -> Inlines -> Inlines) -> F Inlines @@ -1913,7 +1922,9 @@ spanHtml = try $ do let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"] return $ if isSmallCaps (ident, classes, keyvals) then B.smallcaps <$> contents - else B.spanWith (ident, classes, keyvals) <$> contents + else if isUnderline (ident, classes, keyvals) + then B.underline <$> contents + else B.spanWith (ident, classes, keyvals) <$> contents divHtml :: PandocMonad m => MarkdownParser m (F Blocks) divHtml = try $ do diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 987028910..751a37808 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -29,7 +29,7 @@ import qualified Data.Set as Set import Data.Maybe (fromMaybe, isNothing, maybeToList) import Data.Text (Text) import qualified Data.Text as T -import Text.Pandoc.Builder (Blocks, Inlines) +import Text.Pandoc.Builder (Blocks, Inlines, underline) import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class.PandocMonad (PandocMonad (..)) import Text.Pandoc.Definition @@ -37,7 +37,7 @@ import Text.Pandoc.Error (PandocError (PandocParsecError)) import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (F) -import Text.Pandoc.Shared (crFilter, trimr, underlineSpan, tshow) +import Text.Pandoc.Shared (crFilter, trimr, tshow) -- | Read Muse from an input string and return a Pandoc document. readMuse :: PandocMonad m @@ -849,7 +849,7 @@ emph = fmap B.emph <$> emphasisBetween (char '*' <* notFollowedBy (char '*')) -- | Parse underline inline markup, indicated by @_@. -- Supported only in Emacs Muse mode, not Text::Amuse. underlined :: PandocMonad m => MuseParser m (F Inlines) -underlined = fmap underlineSpan +underlined = fmap underline <$ guardDisabled Ext_amuse -- Supported only by Emacs Muse <*> emphasisBetween (char '_') diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index cbf7236d0..74120f96a 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -37,7 +37,7 @@ import Data.Semigroup (First(..), Option(..)) import Text.TeXMath (readMathML, writeTeX) import qualified Text.XML.Light as XML -import Text.Pandoc.Builder +import Text.Pandoc.Builder hiding (underline) import Text.Pandoc.MediaBag (MediaBag, insertMedia) import Text.Pandoc.Shared import Text.Pandoc.Extensions (extensionsFromList, Extension(..)) diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 9ac74f192..1055cd0db 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -27,7 +27,6 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline) -import Text.Pandoc.Shared (underlineSpan) import Text.TeXMath (DisplayType (..), readTeX, writePandoc) import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap @@ -567,7 +566,7 @@ strikeout :: PandocMonad m => OrgParser m (F Inlines) strikeout = fmap B.strikeout <$> emphasisBetween '+' underline :: PandocMonad m => OrgParser m (F Inlines) -underline = fmap underlineSpan <$> emphasisBetween '_' +underline = fmap B.underline <$> emphasisBetween '_' verbatim :: PandocMonad m => OrgParser m (F Inlines) verbatim = return . B.code <$> verbatimBetween '=' diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index fef192fd3..598420a0d 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -52,7 +52,7 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag) import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline) -import Text.Pandoc.Shared (crFilter, trim, underlineSpan, tshow) +import Text.Pandoc.Shared (crFilter, trim, tshow) -- | Parse a Textile text and return a Pandoc document. readTextile :: PandocMonad m @@ -451,7 +451,7 @@ inlineMarkup = choice [ simpleInline (string "??") (B.cite []) , simpleInline (string "__") B.emph , simpleInline (char '*') B.strong , simpleInline (char '_') B.emph - , simpleInline (char '+') underlineSpan + , simpleInline (char '+') B.underline , simpleInline (char '-' <* notFollowedBy (char '-')) B.strikeout , simpleInline (char '^') B.superscript , simpleInline (char '~') B.subscript diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index c5c87e471..245df6f08 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -31,8 +31,7 @@ import Data.Time (defaultTimeLocale) import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (space, spaces, uri) -import Text.Pandoc.Shared (compactify, compactifyDL, crFilter, escapeURI, - underlineSpan) +import Text.Pandoc.Shared (compactify, compactifyDL, crFilter, escapeURI) type T2T = ParserT Text ParserState (Reader T2TMeta) @@ -378,7 +377,7 @@ bold :: T2T Inlines bold = inlineMarkup inline B.strong '*' B.str underline :: T2T Inlines -underline = inlineMarkup inline underlineSpan '_' B.str +underline = inlineMarkup inline B.underline '_' B.str strike :: T2T Inlines strike = inlineMarkup inline B.strikeout '-' B.str |