aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2024-04-23 15:00:42 -0700
committerJohn MacFarlane <[email protected]>2024-04-23 15:00:42 -0700
commitb6cff6b96d17082a2fc2306ffd82af5521dfbf29 (patch)
tree375fecdfdb6cb64baeaf663a56698920633cc0e6 /src/Text
parent88eff1473225c5d4d287ed30470a4ec8eef4bc84 (diff)
Docx reader: issue warning rather than error...
when we can't parse EndNote citations. See #8433.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs18
-rw-r--r--src/Text/Pandoc/Readers/EndNote.hs6
2 files changed, 15 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 7752092b1..823c8537f 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -2,6 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Readers.Docx
@@ -92,7 +93,7 @@ import Text.Pandoc.Readers.Docx.Parse as Docx
import Text.Pandoc.Shared
import Text.Pandoc.Walk
import Text.TeXMath (writeTeX)
-import Control.Monad.Except (throwError)
+import Control.Monad.Except (throwError, catchError)
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import qualified Text.Pandoc.Class.PandocMonad as P
import Text.Pandoc.Error
@@ -103,7 +104,6 @@ import qualified Data.Text.Lazy as TL
import Text.Pandoc.UTF8 (fromTextLazy)
import Text.Pandoc.Citeproc.MetaValue (referenceToMetaValue)
import Text.Pandoc.Readers.EndNote (readEndNoteXMLCitation)
-import Text.Pandoc.Sources (toSources)
readDocx :: PandocMonad m
=> ReaderOptions
@@ -477,10 +477,16 @@ parPartToInlines' (Field info children) =
formattedCite <- smushInlines <$> mapM parPartToInlines' children
opts <- asks docxOptions
if isEnabled Ext_citations opts
- then do
- citation <- readEndNoteXMLCitation (toSources t)
- cs <- handleCitation citation
- return $ cite cs formattedCite
+ then catchError
+ (do citation <- readEndNoteXMLCitation t
+ cs <- handleCitation citation
+ return $ cite cs formattedCite)
+ (\case
+ PandocXMLError _ msg -> do
+ P.report $ DocxParserWarning
+ ("Cannot parse EndNote citation: " <> msg)
+ return formattedCite
+ e -> throwError e)
else return formattedCite
CslCitation t -> do
formattedCite <- smushInlines <$> mapM parPartToInlines' children
diff --git a/src/Text/Pandoc/Readers/EndNote.hs b/src/Text/Pandoc/Readers/EndNote.hs
index 56a9dc0be..a35e5750e 100644
--- a/src/Text/Pandoc/Readers/EndNote.hs
+++ b/src/Text/Pandoc/Readers/EndNote.hs
@@ -72,10 +72,10 @@ readEndNoteXML _opts inp = do
B.doc mempty
readEndNoteXMLCitation :: PandocMonad m
- => Sources -> m (Citeproc.Citation Text)
-readEndNoteXMLCitation sources = do
+ => Text -> m (Citeproc.Citation Text)
+readEndNoteXMLCitation xml = do
tree <- either (throwError . PandocXMLError "EndNote references") return $
- parseXMLElement (TL.fromStrict . sourcesToText $ sources)
+ parseXMLElement (TL.fromStrict xml)
unless (qName (elName tree) == "EndNote") $
throwError $ PandocXMLError "EndNote references" "Expected EndNote element"
let items = map toCitationItem $ filterElementsName (name "Cite") tree