diff options
| author | John MacFarlane <[email protected]> | 2023-06-30 13:54:26 -0700 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2023-06-30 13:54:26 -0700 |
| commit | 4031efca34b71f04fe3c3ed9fbb2fc8e468e857d (patch) | |
| tree | 28589318101a58c2993eb283b976ba68161ad34e | |
| parent | 26a90162f0772b4545fe51ea190cf04c8435f1aa (diff) | |
Typst reader: improve info message for skipped elements.
| -rw-r--r-- | src/Text/Pandoc/Readers/Typst.hs | 10 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Typst/Math.hs | 24 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Typst/Parsing.hs | 6 |
3 files changed, 28 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Readers/Typst.hs b/src/Text/Pandoc/Readers/Typst.hs index bec7e8a1f..7034d45b0 100644 --- a/src/Text/Pandoc/Readers/Typst.hs +++ b/src/Text/Pandoc/Readers/Typst.hs @@ -43,7 +43,7 @@ import Text.Parsec import Text.TeXMath (writeTeX) import Text.TeXMath.Shared (getSpaceChars) import Text.Pandoc.Readers.Typst.Math (pMathMany) -import Text.Pandoc.Readers.Typst.Parsing (pTok, warn, chunks, getField, P) +import Text.Pandoc.Readers.Typst.Parsing (pTok, ignored, chunks, getField, P) import Typst.Methods (applyPureFunction, formatNumber) import Typst.Types @@ -165,7 +165,7 @@ handleBlock tok = do B.divWith (fromMaybe "" mbident, [], []) <$> (getField "body" fields >>= pWithContents pBlocks) Elt "place" pos fields -> do - warn "Ignoring parameters of place" + ignored "parameters of place" handleBlock (Elt "block" pos fields) Elt "columns" _ fields -> do (cnt :: Integer) <- getField "count" fields @@ -304,7 +304,7 @@ handleBlock tok = do Elt "footnote.entry" _ fields -> getField "body" fields >>= pWithContents pBlocks Elt (Identifier tname) _ _ -> do - warn ("Skipping unknown block element " <> tname) + ignored ("unknown block element " <> tname) pure mempty pPara :: PandocMonad m => P m B.Blocks @@ -456,7 +456,7 @@ handleInline tok = VString t -> pure t VLabel t -> pure $ "#" <> t VDict _ -> do - warn "Unable to link to location, linking to #" + ignored "link to location, linking to #" pure "#" _ -> fail $ "Expected string or label for dest" body <- getField "body" fields @@ -512,7 +512,7 @@ handleInline tok = | "math." `T.isPrefixOf` tname -> B.math . writeTeX <$> pMathMany (Seq.singleton tok) Elt (Identifier tname) _ _ -> do - warn ("Skipping unknown inline element " <> tname) + ignored ("unknown inline element " <> tname) pure mempty modString :: (Text -> Text) -> B.Inline -> B.Inline diff --git a/src/Text/Pandoc/Readers/Typst/Math.hs b/src/Text/Pandoc/Readers/Typst/Math.hs index b6b7f29b2..8256843c1 100644 --- a/src/Text/Pandoc/Readers/Typst/Math.hs +++ b/src/Text/Pandoc/Readers/Typst/Math.hs @@ -28,7 +28,7 @@ import Text.TeXMath.Types ) import Text.TeXMath.Unicode.ToTeX (getSymbolType) import Text.Pandoc.Readers.Typst.Parsing - ( P, pTok, warn, pWithContents, getField, chunks ) + ( P, pTok, ignored, pWithContents, getField, chunks ) import Typst.Types -- import Debug.Trace @@ -55,7 +55,7 @@ handleMath :: PandocMonad m => Content -> P m Exp handleMath tok = case tok of Lab t -> do - warn ("skipping label " <> t) + ignored ("label " <> t) pure (EGrouped []) Txt t | T.any isDigit t -> pure $ ENumber t @@ -312,11 +312,27 @@ handleMath tok = Elt "table" pos fields -> handleMath (Elt "grid" pos fields) Elt "link" _ fields -> do body <- getField "body" fields - warn "Hyperlinks not supported in math" + ignored "hyperlink in math" pMathGrouped body + Elt "math.display" _ fields -> do + content <- getField "content" fields + ignored "display" + pMathGrouped content + Elt "math.inline" _ fields -> do + content <- getField "content" fields + ignored "inline" + pMathGrouped content + Elt "math.script" _ fields -> do + content <- getField "content" fields + ignored "script" + pMathGrouped content + Elt "math.sscript" _ fields -> do + content <- getField "content" fields + ignored "sscript" + pMathGrouped content Elt (Identifier name) _ fields -> do body <- getField "body" fields `mplus` pure mempty - warn ("Ignoring unsupported " <> name) + ignored name pMathGrouped body arrayDelims :: PandocMonad m => M.Map Identifier Val -> P m (Text, Text) diff --git a/src/Text/Pandoc/Readers/Typst/Parsing.hs b/src/Text/Pandoc/Readers/Typst/Parsing.hs index 585cc34a0..613183f25 100644 --- a/src/Text/Pandoc/Readers/Typst/Parsing.hs +++ b/src/Text/Pandoc/Readers/Typst/Parsing.hs @@ -7,7 +7,7 @@ module Text.Pandoc.Readers.Typst.Parsing ( P, pTok, pWithContents, - warn, + ignored, getField, chunks, ) @@ -36,8 +36,8 @@ pTok f = tokenPrim show showPos match match x | f x = Just x match _ = Nothing -warn :: PandocMonad m => Text -> P m () -warn msg = lift $ report $ IgnoredElement msg +ignored :: PandocMonad m => Text -> P m () +ignored msg = lift $ report $ IgnoredElement msg pWithContents :: PandocMonad m => P m a -> Seq Content -> P m a pWithContents pa cs = do |
