aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-10-03 19:11:12 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2021-10-05 08:44:51 -0700
commit6c507a66cf007ee0d7739ef4c4217f6984db49ef (patch)
tree9170b79009fe4ecf55cf288e2f813b72947e1b5f
parentb8d460eeabe97756d49e4bc5f00c6bb084b69aa5 (diff)
downloadpandoc-6c507a66cf007ee0d7739ef4c4217f6984db49ef.tar.gz
Avoid bad wraps in markdown writer at the Doc Text level.
Previously we tried to do this at the Inline list level, but it makes more sense to intervene on breaking spaces at the Doc Text level.
-rw-r--r--src/Text/Pandoc/Writers/Markdown/Inline.hs45
1 files changed, 23 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Writers/Markdown/Inline.hs b/src/Text/Pandoc/Writers/Markdown/Inline.hs
index 31c816e36..ab9674026 100644
--- a/src/Text/Pandoc/Writers/Markdown/Inline.hs
+++ b/src/Text/Pandoc/Writers/Markdown/Inline.hs
@@ -190,11 +190,13 @@ getReference attr label target = do
(stKeys s) })
return lab'
+
+
-- | Convert list of Pandoc inline elements to markdown.
inlineListToMarkdown :: PandocMonad m => WriterOptions -> [Inline] -> MD m (Doc Text)
-inlineListToMarkdown opts lst = do
- inlist <- asks envInList
- go (if inlist then avoidBadWrapsInList lst else lst)
+inlineListToMarkdown opts ils = do
+ inlist <- asks envInList
+ avoidBadWraps inlist <$> go ils
where go [] = return empty
go (x@Math{}:y@(Str t):zs)
| T.all isDigit (T.take 1 t) -- starts with digit -- see #7058
@@ -235,26 +237,25 @@ inlineListToMarkdown opts lst = do
fmap (iMark <>) (go is)
thead = fmap fst . T.uncons
-isSp :: Inline -> Bool
-isSp Space = True
-isSp SoftBreak = True
-isSp _ = False
+-- Remove breaking spaces that might cause bad wraps.
+avoidBadWraps :: Bool -> Doc Text -> Doc Text
+avoidBadWraps inListItem = go . toList
+ where
+ go [] = mempty
+ go (BreakingSpace : Text len t : BreakingSpace : xs)
+ = case T.uncons t of
+ Just (c,t')
+ | c == '>'
+ || ((c == '-' || c == '*' || c == '+') && T.null t')
+ || (inListItem && isOrderedListMarker t)
+ || (t == "1." || t == "1)")
+ -> Text (len + 1) (" " <> t) <> go (BreakingSpace : xs)
+ _ -> BreakingSpace <> Text len t <> go (BreakingSpace : xs)
+ go (x:xs) = x <> go xs
-avoidBadWrapsInList :: [Inline] -> [Inline]
-avoidBadWrapsInList [] = []
-avoidBadWrapsInList (s:Str (T.uncons -> Just ('>',cs)):xs) | isSp s =
- Str (" >" <> cs) : avoidBadWrapsInList xs
-avoidBadWrapsInList [s, Str (T.uncons -> Just (c, cs))]
- | T.null cs && isSp s && c `elem` ['-','*','+'] = [Str $ T.pack [' ', c]]
-avoidBadWrapsInList (s:Str (T.uncons -> Just (c, cs)):Space:xs)
- | T.null cs && isSp s && c `elem` ['-','*','+'] =
- Str (T.pack [' ', c]) : Space : avoidBadWrapsInList xs
-avoidBadWrapsInList (s:Str cs:Space:xs)
- | isSp s && isOrderedListMarker cs =
- Str (" " <> cs) : Space : avoidBadWrapsInList xs
-avoidBadWrapsInList [s, Str cs]
- | isSp s && isOrderedListMarker cs = [Str $ " " <> cs]
-avoidBadWrapsInList (x:xs) = x : avoidBadWrapsInList xs
+ toList (Concat (Concat a b) c) = toList (Concat a (Concat b c))
+ toList (Concat a b) = a : toList b
+ toList x = [x]
isOrderedListMarker :: Text -> Bool
isOrderedListMarker xs = not (T.null xs) && (T.last xs `elem` ['.',')']) &&