aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2025-02-27 13:37:25 -0800
committerJohn MacFarlane <[email protected]>2025-02-27 13:37:25 -0800
commitac799380434ac72029d0b4a6412dcbd2941036c7 (patch)
treebf41b59a086976bfada76d3e53587e2f748cae21 /src
parent954067474d3dcbca4921863b7b566cbf718f6b72 (diff)
Typst writer: better heuristics for escaping potential list markers.
Closes #10650.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/Typst.hs43
1 files changed, 29 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Writers/Typst.hs b/src/Text/Pandoc/Writers/Typst.hs
index c935825f4..fdfad0f20 100644
--- a/src/Text/Pandoc/Writers/Typst.hs
+++ b/src/Text/Pandoc/Writers/Typst.hs
@@ -29,8 +29,7 @@ import Network.URI (unEscapeString)
import qualified Data.Text as T
import Control.Monad.State ( StateT, evalStateT, gets, modify )
import Text.Pandoc.Writers.Shared ( metaToContext, defField, resetField,
- lookupMetaString,
- isOrderedListMarker )
+ lookupMetaString )
import Text.Pandoc.Shared (isTightList, orderedListMarkers, tshow)
import Text.Pandoc.Writers.Math (convertMath)
import qualified Text.TeXMath as TM
@@ -39,7 +38,7 @@ import Text.DocTemplates (renderTemplate)
import Text.Pandoc.Extensions (Extension(..))
import Text.Collate.Lang (Lang(..), parseLang)
import Text.Printf (printf)
-import Data.Char (isAlphaNum)
+import Data.Char (isAlphaNum, isDigit)
import Data.Maybe (fromMaybe)
-- | Convert Pandoc to Typst.
@@ -147,8 +146,12 @@ blocksToTypst blocks = vcat <$> mapM blockToTypst blocks
blockToTypst :: PandocMonad m => Block -> TW m (Doc Text)
blockToTypst block =
case block of
- Plain inlines -> inlinesToTypst inlines
- Para inlines -> ($$ blankline) <$> inlinesToTypst inlines
+ Plain inlines -> do
+ opts <- gets stOptions
+ inlinesToTypst (addLineStartEscapes opts inlines)
+ Para inlines -> do
+ opts <- gets stOptions
+ ($$ blankline) <$> inlinesToTypst (addLineStartEscapes opts inlines)
Header level (ident,cls,_) inlines -> do
contents <- inlinesToTypst inlines
let lab = toLabel FreestandingLabel ident
@@ -474,16 +477,28 @@ mkImage opts useBox src attr
| otherwise = "image" <> parens (doubleQuoted src' <> dimAttrs)
textstyle :: PandocMonad m => Doc Text -> [Inline] -> TW m (Doc Text)
-textstyle s inlines =
- (<> endCode) . (s <>) . brackets . addEscape <$> inlinesToTypst inlines
+textstyle s inlines = do
+ opts <- gets stOptions
+ (<> endCode) . (s <>) . brackets
+ <$> inlinesToTypst (addLineStartEscapes opts inlines)
+
+addLineStartEscapes :: WriterOptions -> [Inline] -> [Inline]
+addLineStartEscapes opts = go True
where
- addEscape =
- case inlines of
- (Str t : _)
- | isOrderedListMarker t -> ("\\" <>)
- | Just (c, _) <- T.uncons t
- , needsEscapeAtLineStart c -> ("\\" <>)
- _ -> id
+ 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 _ [] = []
+
+isOrderedListMarker :: Text -> Bool
+isOrderedListMarker t = not (T.null ds) && rest == "."
+ where (ds, rest) = T.span isDigit t
escapeTypst :: Bool -> EscapeContext -> Text -> Doc Text
escapeTypst smart context t =