aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2025-06-05 14:39:16 -0700
committerJohn MacFarlane <[email protected]>2025-06-05 14:39:16 -0700
commit58daa8e2e828cd17cc20bc02608b76a5ba086d30 (patch)
tree3a560622ab8dd546e1b05ebe753b88f9cd483773
parentccec1e0b65dad97765303e9640b40503961d32ca (diff)
ANSI writer: make `--wrap=none` work properly.
Closes #10898.
-rw-r--r--src/Text/Pandoc/Writers/ANSI.hs31
1 files changed, 22 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Writers/ANSI.hs b/src/Text/Pandoc/Writers/ANSI.hs
index b12f3d412..6a2b89737 100644
--- a/src/Text/Pandoc/Writers/ANSI.hs
+++ b/src/Text/Pandoc/Writers/ANSI.hs
@@ -76,26 +76,39 @@ pandocToANSI opts (Pandoc meta blocks) = do
metadata <- metaToContext opts
(blockListToANSI opts)
(inlineListToANSI opts) meta
- width <- gets stColumns
- let title = titleBlock width metadata
+ let colwidth = if writerWrapText opts == WrapAuto
+ then Just $ writerColumns opts
+ else Nothing
+ let title = titleBlock colwidth metadata
let blocks' = makeSections (writerNumberSections opts) Nothing blocks
body <- blockListToANSI opts blocks'
notes <- gets $ reverse . stNotes
let notemark x = D.literal (tshow (x :: Int) <> ".") <+> D.space
let marks = map notemark [1..length notes]
let hangWidth = foldr (max . D.offset) 0 marks
- let notepretty | not (null notes) = D.cblock width hr $+$ hangMarks hangWidth marks notes
- | otherwise = D.empty
+ let notepretty
+ | not (null notes) =
+ (case colwidth of
+ Nothing -> hr
+ Just w -> D.cblock w hr)
+ $+$ hangMarks hangWidth marks notes
+ | otherwise = D.empty
let main = body $+$ notepretty
let context = defField "body" main
$ defField "titleblock" title metadata
return $
case writerTemplate opts of
- Nothing -> toStrict $ D.renderANSI (Just width) main
- Just tpl -> toStrict $ D.renderANSI (Just width) $ renderTemplate tpl context
-
-titleBlock :: Int -> Context Text -> D.Doc Text
-titleBlock width meta = if null most then D.empty else D.cblock width $ most $+$ hr
+ Nothing -> toStrict $ D.renderANSI colwidth main
+ Just tpl -> toStrict $ D.renderANSI colwidth
+ $ renderTemplate tpl context
+
+titleBlock :: Maybe Int -> Context Text -> D.Doc Text
+titleBlock width meta =
+ if null most
+ then D.empty
+ else (case width of
+ Just w -> D.cblock w
+ Nothing -> id) $ most $+$ hr
where
title = D.bold (fromMaybe D.empty $ getField "title" meta)
subtitle = fromMaybe D.empty $ getField "subtitle" meta