From 2c857d379beea55210d7e130402e10a7e7b5e23c Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 16 Aug 2025 19:21:39 -0700 Subject: Typst writer: add escapes to prevent inadvertent lists... due to automatic wrapping. Also simplify existing code that was meant to do this. Closes #10047. --- src/Text/Pandoc/Writers/Typst.hs | 44 ++++++++++++++++------------------------ test/command/10047.md | 7 +++++++ 2 files changed, 25 insertions(+), 26 deletions(-) create mode 100644 test/command/10047.md diff --git a/src/Text/Pandoc/Writers/Typst.hs b/src/Text/Pandoc/Writers/Typst.hs index a5cdbc483..e4db9ffc6 100644 --- a/src/Text/Pandoc/Writers/Typst.hs +++ b/src/Text/Pandoc/Writers/Typst.hs @@ -1,5 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} {- | Module : Text.Pandoc.Writers.Typst @@ -77,9 +78,9 @@ pandocToTypst options (Pandoc meta blocks) = do let toPosition :: CaptionPosition -> Text toPosition CaptionAbove = "top" toPosition CaptionBelow = "bottom" - let nociteIds = query (\inln -> case inln of - Cite cs _ -> map citationId cs - _ -> []) + let nociteIds = query (\case + Cite cs _ -> map citationId cs + _ -> []) $ lookupMetaInlines "nocite" meta let context = defField "body" main @@ -160,12 +161,9 @@ blocksToTypst blocks = vcat <$> mapM blockToTypst blocks blockToTypst :: PandocMonad m => Block -> TW m (Doc Text) blockToTypst block = case block of - Plain inlines -> do - opts <- gets stOptions - inlinesToTypst (addLineStartEscapes opts inlines) + Plain inlines -> inlinesToTypst inlines Para inlines -> do - opts <- gets stOptions - ($$ blankline) <$> inlinesToTypst (addLineStartEscapes opts inlines) + ($$ blankline) <$> inlinesToTypst inlines Header level (ident,cls,_) inlines -> do contents <- inlinesToTypst inlines let lab = toLabel FreestandingLabel ident @@ -504,23 +502,17 @@ mkImage opts useBox src attr textstyle :: PandocMonad m => Doc Text -> [Inline] -> TW m (Doc Text) textstyle s inlines = do - opts <- gets stOptions - (<> endCode) . (s <>) . brackets - <$> inlinesToTypst (addLineStartEscapes opts inlines) - -addLineStartEscapes :: WriterOptions -> [Inline] -> [Inline] -addLineStartEscapes opts = go True - where - go True (Str t : xs) - | isOrderedListMarker t = RawInline "typst" "\\" : Str t : go False xs - | Just (c, t') <- T.uncons t - , needsEscapeAtLineStart c - , T.null t' = RawInline "typst" "\\" : Str t : go False xs - go _ (SoftBreak : xs) - | writerWrapText opts == WrapPreserve = SoftBreak : go True xs - go _ (LineBreak : xs) = LineBreak : go True xs - go _ (x : xs) = x : go False xs - go _ [] = [] + (<> endCode) . (s <>) . brackets . fixInitialAfterBreakEscape + <$> inlinesToTypst inlines + +fixInitialAfterBreakEscape :: Doc Text -> Doc Text +fixInitialAfterBreakEscape (Concat x y) = + Concat (fixInitialAfterBreakEscape x) y +-- make an initial AfterBreak escape unconditional (it will be rendered +-- in a block [..] and there won't be an actual break to trigger it, but +-- typst still needs the escape) +fixInitialAfterBreakEscape (AfterBreak "\\") = Text 1 "\\" +fixInitialAfterBreakEscape x = x isOrderedListMarker :: Text -> Bool isOrderedListMarker t = not (T.null ds) && rest == "." @@ -530,7 +522,7 @@ escapeTypst :: Bool -> EscapeContext -> Text -> Doc Text escapeTypst smart context t = (case T.uncons t of Just (c, _) - | needsEscapeAtLineStart c + | needsEscapeAtLineStart c || isOrderedListMarker t -> afterBreak "\\" _ -> mempty) <> (literal (T.replace "//" "\\/\\/" diff --git a/test/command/10047.md b/test/command/10047.md new file mode 100644 index 000000000..c651a1b43 --- /dev/null +++ b/test/command/10047.md @@ -0,0 +1,7 @@ +``` +% pandoc -t typst --wrap=auto +Full-time study: 2001-2003; Thesis submission: Nov 2005; Award: Jul 2006. +^D +Full-time study: 2001-2003; Thesis submission: Nov 2005; Award: Jul +\2006. +``` -- cgit v1.2.3