aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs12
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs11
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs9
3 files changed, 14 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index bf01f663b..12444f75f 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -1548,6 +1548,9 @@ inlineToHtml opts inline = do
_ -> do report $ InlineNotRendered inline
return mempty
(Link attr txt (s,_)) | "mailto:" `T.isPrefixOf` s -> do
+ -- We need to remove links from link text, because an
+ -- <a> element is not allowed inside another <a>
+ -- element.
linkText <- inlineListToHtml opts (removeLinks txt)
obfuscateLink opts attr linkText s
(Link (ident,classes,kvs) txt (s,tit)) -> do
@@ -1768,15 +1771,6 @@ isSlideVariant :: Format -> Bool
isSlideVariant f = f `elem` [Format "s5", Format "slidy", Format "slideous",
Format "dzslides", Format "revealjs"]
-
--- We need to remove links from link text, because an <a> element is
--- not allowed inside another <a> element.
-removeLinks :: [Inline] -> [Inline]
-removeLinks = walk go
- where
- go (Link attr ils _) = Span attr ils
- go x = x
-
toURI :: Bool -> Text -> Text
toURI isHtml5 t = if isHtml5 then t else escapeURI t
where
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 2991e4ebc..d85354756 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -26,7 +26,6 @@ import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.Options
-import Text.Pandoc.Walk
import Text.DocLayout (render, literal)
import Text.Pandoc.Shared
import Text.Pandoc.URI
@@ -484,6 +483,8 @@ inlineToMediaWiki SoftBreak = do
inlineToMediaWiki Space = return " "
inlineToMediaWiki (Link _ txt (src, _)) = do
+ -- We need to remove links from link text, because an <a> element is
+ -- not allowed inside another <a> element.
label <- inlineListToMediaWiki (removeLinks txt)
case txt of
[Str s] | isURI src && escapeURI s == src -> return src
@@ -518,14 +519,6 @@ inlineToMediaWiki (Note contents) = do
return $ "<ref>" <> stripTrailingNewlines contents' <> "</ref>"
-- note - does not work for notes with multiple blocks
--- We need to remove links from link text, because an <a> element is
--- not allowed inside another <a> element.
-removeLinks :: [Inline] -> [Inline]
-removeLinks = walk go
- where
- go (Link _ ils _) = SmallCaps ils
- go x = x
-
highlightingLangs :: Set.Set Text
highlightingLangs = Set.fromList [
"abap",
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index aff1520f1..9d71f2fb3 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -45,6 +45,7 @@ module Text.Pandoc.Writers.Shared (
, toLegacyTable
, splitSentences
, ensureValidXmlIdentifiers
+ , removeLinks
, setupTranslations
, isOrderedListMarker
, toTaskListItem
@@ -805,6 +806,14 @@ walkAttr f = walk goInline . walk goBlock
goBlock (Div attr bs) = Div (f attr) bs
goBlock x = x
+-- | Convert links to spans; most useful when writing elements that must not
+-- contain links, e.g. to avoid nested links.
+removeLinks :: [Inline] -> [Inline]
+removeLinks = walk go
+ where
+ go (Link attr ils _) = Span attr ils
+ go x = x
+
-- | Set translations based on the `lang` in metadata.
setupTranslations :: PandocMonad m => Meta -> m ()
setupTranslations meta = do