Skip to content

Commit d8b5541

Browse files
committed
Typst reader: allow @refs to become citations...
if there is no corresponding label in the document.
1 parent cafca39 commit d8b5541

File tree

2 files changed

+41
-12
lines changed

2 files changed

+41
-12
lines changed

src/Text/Pandoc/Readers/Typst.hs

Lines changed: 39 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -68,10 +68,13 @@ readTypst _opts inp = do
6868
currentUTCTime = getCurrentTime,
6969
lookupEnvVar = fmap (fmap T.unpack) . lookupEnv . T.pack,
7070
checkExistence = fileExists }
71-
evaluateTypst ops inputName parsed >>=
72-
either (throwError . PandocParseError . T.pack . show) pure >>=
73-
runParserT pPandoc () inputName . F.toList >>=
74-
either (throwError . PandocParseError . T.pack . show) pure
71+
res <- evaluateTypst ops inputName parsed
72+
case res of
73+
Left e -> throwError $ PandocParseError $ tshow e
74+
Right cs -> do
75+
let labs = findLabels cs
76+
runParserT pPandoc labs inputName (F.toList cs) >>=
77+
either (throwError . PandocParseError . T.pack . show) pure
7578

7679
pBlockElt :: PandocMonad m => P m B.Blocks
7780
pBlockElt = try $ do
@@ -98,13 +101,29 @@ pInline = try $ do
98101
| "math." `T.isPrefixOf` tname
99102
, tname /= "math.equation" ->
100103
B.math . writeTeX <$> pMathMany (Seq.singleton res)
101-
Elt name@(Identifier tname) pos fields ->
102-
case M.lookup name inlineHandlers of
103-
Nothing -> do
104-
ignored ("unknown inline element " <> tname <>
105-
" at " <> tshow pos)
106-
pure mempty
107-
Just handler -> handler Nothing fields
104+
Elt name@(Identifier tname) pos fields -> do
105+
labs <- getState
106+
labelTarget <- (do VLabel t <- getField "target" fields
107+
True <$ guard (t `elem` labs))
108+
<|> pure False
109+
if tname == "ref" && not labelTarget
110+
then do
111+
-- @foo is a citation unless it links to a lab in the doc:
112+
let targetToKey (Identifier "target") = Identifier "key"
113+
targetToKey k = k
114+
case M.lookup "cite" inlineHandlers of
115+
Nothing -> do
116+
ignored ("unknown inline element " <> tname <>
117+
" at " <> tshow pos)
118+
pure mempty
119+
Just handler -> handler Nothing (M.mapKeys targetToKey fields)
120+
else do
121+
case M.lookup name inlineHandlers of
122+
Nothing -> do
123+
ignored ("unknown inline element " <> tname <>
124+
" at " <> tshow pos)
125+
pure mempty
126+
Just handler -> handler Nothing fields
108127

109128
pPandoc :: PandocMonad m => P m B.Pandoc
110129
pPandoc = B.doc <$> pBlocks
@@ -547,3 +566,12 @@ collapseAdjacentCites = B.fromList . foldr go [] . B.toList
547566
modString :: (Text -> Text) -> B.Inline -> B.Inline
548567
modString f (B.Str t) = B.Str (f t)
549568
modString _ x = x
569+
570+
findLabels :: Seq.Seq Content -> [Text]
571+
findLabels = foldr go []
572+
where
573+
go (Txt{}) = id
574+
go (Lab t) = (t :)
575+
go (Elt{ eltFields = fs }) = \ts -> foldr go' ts fs
576+
go' (VContent cs) = (findLabels cs ++)
577+
go' _ = id

src/Text/Pandoc/Readers/Typst/Parsing.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,8 @@ import Typst.Types
2626
import Text.Pandoc.Class.PandocMonad ( PandocMonad, report )
2727
import Text.Pandoc.Logging (LogMessage(..))
2828

29-
type P m a = ParsecT [Content] () m a
29+
type P m a = ParsecT [Content] [Text] m a
30+
-- state tracks a list of labels in the document
3031

3132
pTok :: PandocMonad m => (Content -> Bool) -> P m Content
3233
pTok f = tokenPrim show showPos match

0 commit comments

Comments
 (0)