aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2025-10-05 16:33:03 +0200
committerJohn MacFarlane <[email protected]>2025-10-05 16:33:03 +0200
commite87b86261f9b0b9dc4df053208c7f6be6621b72a (patch)
tree9e729b72b3ced5a45368a5d6d7c6d0393d4431c6 /src
parent208142fcf2b3b255b9cb55d2062b6602b9e14780 (diff)
Typst writer: don't add semicolons as much.
Previously we added semicolons after inline commands not followed by spaces, but mainly this was to deal with one issue: the presence of a semicolon after an inline command, which would be swallowed as a command separator (#9252). This commits adopts an approach that should avoid so many superfluous semicolons: it escapes semicolons that might come right after a command. See #11196.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/Typst.hs16
1 files changed, 6 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Writers/Typst.hs b/src/Text/Pandoc/Writers/Typst.hs
index 52a853b7f..40e1f3ac8 100644
--- a/src/Text/Pandoc/Writers/Typst.hs
+++ b/src/Text/Pandoc/Writers/Typst.hs
@@ -443,9 +443,8 @@ inlineToTypst inline =
case cls of
(lang:_) | writerHighlightMethod opts /= NoHighlighting
-> "#raw(lang:" <> doubleQuoted lang <>
- ", " <> doubleQuoted code <> ")" <> endCode
+ ", " <> doubleQuoted code <> ")"
_ | T.any (=='`') code -> "#raw(" <> doubleQuoted code <> ")"
- <> endCode
| otherwise -> "`" <> literal code <> "`"
case writerHighlightMethod opts of
Skylighting _ ->
@@ -503,7 +502,6 @@ inlineToTypst inline =
-> if T.all isIdentChar ident
then pure $ literal $ "@" <> ident
else pure $ "#ref" <> parens (toLabel ArgumentLabel ident)
- <> endCode
_ -> do
contents <- inlinesToTypst inlines
let dest = case T.uncons src of
@@ -512,13 +510,13 @@ inlineToTypst inline =
pure $ "#link" <> parens dest <>
(if inlines == [Str src]
then mempty
- else nowrap $ brackets contents) <> endCode
+ else nowrap $ brackets contents)
Image attr _inlines (src,_tit) -> do
opts <- gets stOptions
pure $ mkImage opts True src attr
Note blocks -> do
contents <- blocksToTypst blocks
- return $ "#footnote" <> brackets (chomp contents) <> endCode
+ return $ "#footnote" <> brackets (chomp contents)
-- see #9104; need box or image is treated as block-level
mkImage :: WriterOptions -> Bool -> Text -> Attr -> Doc Text
@@ -544,7 +542,7 @@ mkImage opts useBox src attr
textstyle :: PandocMonad m => Doc Text -> [Inline] -> TW m (Doc Text)
textstyle s inlines = do
- (<> endCode) . (s <>) . brackets . fixInitialAfterBreakEscape
+ (s <>) . brackets . fixInitialAfterBreakEscape
<$> inlinesToTypst inlines
fixInitialAfterBreakEscape :: Doc Text -> Doc Text
@@ -564,6 +562,7 @@ escapeTypst :: Bool -> EscapeContext -> Text -> Doc Text
escapeTypst smart context t =
(case T.uncons t of
Just (c, _)
+ | c == ';' -> char '\\' -- see #9252
| needsEscapeAtLineStart c || isOrderedListMarker t
-> afterBreak "\\"
_ -> mempty) <>
@@ -654,7 +653,7 @@ toCite cite = do
pure $ (if citationMode cite == SuppressAuthor -- see #11044
then parens
else id)
- $ "#cite" <> parens (label <> form <> suppl) <> endCode
+ $ "#cite" <> parens (label <> form <> suppl)
doubleQuoted :: Text -> Doc Text
doubleQuoted = doubleQuotes . literal . escape
@@ -664,9 +663,6 @@ doubleQuoted = doubleQuotes . literal . escape
escapeChar '"' = "\\\""
escapeChar c = T.singleton c
-endCode :: Doc Text
-endCode = beforeNonBlank ";"
-
extractLabel :: Text -> Maybe Text
extractLabel = go . T.unpack
where