aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2025-03-17 11:24:38 -0700
committerJohn MacFarlane <[email protected]>2025-03-17 11:24:38 -0700
commit3acd8859bd59b865631707f785207b43cda8314f (patch)
tree6052c3167da2c703b530d44bd7b18df2935273d7
parentf717d1bccc9448b588e279e5f101b2f4963b57a7 (diff)
T.P.Writers.Shared: rename `surroundInlines` -> `delimited`.
-rw-r--r--src/Text/Pandoc/Writers/Markdown/Inline.hs18
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs6
2 files changed, 12 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Writers/Markdown/Inline.hs b/src/Text/Pandoc/Writers/Markdown/Inline.hs
index 0f6c74597..98ac91cba 100644
--- a/src/Text/Pandoc/Writers/Markdown/Inline.hs
+++ b/src/Text/Pandoc/Writers/Markdown/Inline.hs
@@ -372,9 +372,9 @@ inlineToMarkdown opts (Emph lst) = do
contents <- inlineListToMarkdown opts lst
return $ case variant of
PlainText
- | isEnabled Ext_gutenberg opts -> surroundInlines "_" "_" contents
+ | isEnabled Ext_gutenberg opts -> delimited "_" "_" contents
| otherwise -> contents
- _ -> surroundInlines "*" "*" contents
+ _ -> delimited "*" "*" contents
inlineToMarkdown _ (Underline []) = return empty
inlineToMarkdown opts (Underline lst) = do
variant <- asks envVariant
@@ -382,7 +382,7 @@ inlineToMarkdown opts (Underline lst) = do
case variant of
PlainText -> return contents
_ | isEnabled Ext_bracketed_spans opts ->
- return $ surroundInlines "[" "]{.underline}" contents
+ return $ delimited "[" "]{.underline}" contents
| isEnabled Ext_native_spans opts ->
return $ tagWithAttrs "span" ("", ["underline"], [])
<> contents
@@ -401,12 +401,12 @@ inlineToMarkdown opts (Strong lst) = do
else lst
_ -> do
contents <- inlineListToMarkdown opts lst
- return $ surroundInlines "**" "**" contents
+ return $ delimited "**" "**" contents
inlineToMarkdown _ (Strikeout []) = return empty
inlineToMarkdown opts (Strikeout lst) = do
contents <- inlineListToMarkdown opts lst
return $ if isEnabled Ext_strikeout opts
- then surroundInlines "~~" "~~" contents
+ then delimited "~~" "~~" contents
else if isEnabled Ext_raw_html opts
then "<s>" <> contents <> "</s>"
else contents
@@ -415,7 +415,7 @@ inlineToMarkdown opts (Superscript lst) =
local (\env -> env {envEscapeSpaces = envVariant env == Markdown}) $ do
contents <- inlineListToMarkdown opts lst
if isEnabled Ext_superscript opts
- then return $ surroundInlines "^" "^" contents
+ then return $ delimited "^" "^" contents
else if isEnabled Ext_raw_html opts
then return $ "<sup>" <> contents <> "</sup>"
else
@@ -433,7 +433,7 @@ inlineToMarkdown opts (Subscript lst) =
local (\env -> env {envEscapeSpaces = envVariant env == Markdown}) $ do
contents <- inlineListToMarkdown opts lst
if isEnabled Ext_subscript opts
- then return $ surroundInlines "~" "~" contents
+ then return $ delimited "~" "~" contents
else if isEnabled Ext_raw_html opts
then return $ "<sub>" <> contents <> "</sub>"
else
@@ -511,7 +511,7 @@ inlineToMarkdown opts (Math InlineMath str) = do
_ | isEnabled Ext_tex_math_gfm opts ->
return $ "$`" <> literal str <> "`$"
| isEnabled Ext_tex_math_dollars opts ->
- return $ surroundInlines "$" "$" (literal str)
+ return $ delimited "$" "$" (literal str)
| isEnabled Ext_tex_math_single_backslash opts ->
return $ "\\(" <> literal str <> "\\)"
| isEnabled Ext_tex_math_double_backslash opts ->
@@ -540,7 +540,7 @@ inlineToMarkdown opts (Math DisplayMath str) = do
$$ literal str
$$ literal "```") <> cr
| isEnabled Ext_tex_math_dollars opts ->
- return $ surroundInlines "$$" "$$" (literal str)
+ return $ delimited "$$" "$$" (literal str)
| isEnabled Ext_tex_math_single_backslash opts ->
return $ "\\[" <> literal str <> "\\]"
| isEnabled Ext_tex_math_double_backslash opts ->
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index 83e566db5..ee3d78bc9 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -48,7 +48,7 @@ module Text.Pandoc.Writers.Shared (
, setupTranslations
, isOrderedListMarker
, toTaskListItem
- , surroundInlines
+ , delimited
)
where
import Safe (lastMay)
@@ -668,8 +668,8 @@ toTaskListItem _ = mzero
-- with whitespace, export this outside the opener or closer.
-- This is used for formats, like Markdown, which don't allow spaces
-- after opening or before closing delimiters.
-surroundInlines :: Doc Text -> Doc Text -> Doc Text -> Doc Text
-surroundInlines opener closer content =
+delimited :: Doc Text -> Doc Text -> Doc Text -> Doc Text
+delimited opener closer content =
mconcat initialWS <> opener <> mconcat middle <> closer <> mconcat finalWS
where
contents = toList content