aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/Typst.hs30
-rw-r--r--test/command/11017.md9
2 files changed, 35 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Readers/Typst.hs b/src/Text/Pandoc/Readers/Typst.hs
index 948455f09..2307920be 100644
--- a/src/Text/Pandoc/Readers/Typst.hs
+++ b/src/Text/Pandoc/Readers/Typst.hs
@@ -51,8 +51,6 @@ import Typst.Methods (formatNumber, applyPureFunction)
import Typst.Types
import qualified Data.Vector as V
--- import Debug.Trace
-
-- | Read Typst from an input string and return a Pandoc document.
readTypst :: (PandocMonad m, ToSources a)
=> ReaderOptions -> a -> m Pandoc
@@ -73,9 +71,10 @@ readTypst _opts inp = do
case res of
Left e -> throwError $ PandocParseError $ tshow e
Right content -> do
- let labs = findLabels [content]
+ let content' = fixNesting content
+ let labs = findLabels [content']
runParserT pPandoc defaultPState{ sLabels = labs }
- inputName [content] >>=
+ inputName [content'] >>=
either (throwError . PandocParseError . T.pack . show) pure
pBlockElt :: PandocMonad m => P m B.Blocks
@@ -129,6 +128,29 @@ pInline = try $ do
pure mempty
Just handler -> handler Nothing fields
+-- Pull block elements out of inline elements, e.g.
+-- Elt "smallcaps" [ Elt "heading" [..] ] ->
+-- Elt "heading" [ Elt "smallcaps" [..]]. See #11017.
+fixNesting :: Content -> Content
+fixNesting el@(Elt name pos fields)
+ | Just (VContent elts) <- M.lookup "body" fields
+ = let elts' = fmap fixNesting elts
+ fields' = M.insert "body" (VContent elts') fields
+ in if isInline el
+ then case getField "body" fields' of
+ Just ([el'@(Elt name' pos' fields'')] :: Seq Content)
+ | isBlock el'
+ , not (isInline el')
+ , "body" `M.member` fields''
+ -> Elt name' pos' $
+ M.insert "body" (VContent
+ (Seq.singleton
+ (Elt name pos fields'')))
+ fields'
+ _ -> Elt name pos fields'
+ else Elt name pos fields'
+fixNesting x = x
+
pPandoc :: PandocMonad m => P m B.Pandoc
pPandoc = do
Elt "document" _ fields <- pTok isDocument
diff --git a/test/command/11017.md b/test/command/11017.md
new file mode 100644
index 000000000..07f3aca6f
--- /dev/null
+++ b/test/command/11017.md
@@ -0,0 +1,9 @@
+```
+% pandoc -t markdown -f typst
+#show heading: smallcaps
+
+= Introduction
+^D
+# [Introduction]{.smallcaps}
+
+```