Got endnote citations working in docx...
Still to do: prefix, suffix, locator.
This commit is contained in:
parent
28349447cb
commit
19cfe6a907
2 changed files with 53 additions and 44 deletions
|
@ -72,8 +72,8 @@ import Data.Maybe (catMaybes, isJust, fromMaybe, mapMaybe)
|
||||||
import Data.Sequence (ViewL (..), viewl)
|
import Data.Sequence (ViewL (..), viewl)
|
||||||
import qualified Data.Sequence as Seq
|
import qualified Data.Sequence as Seq
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
import Citeproc (ItemId(..), Reference(..), CitationItem(..),
|
import Citeproc (ItemId(..), Reference(..), CitationItem(..))
|
||||||
Citation(citationItems))
|
import qualified Citeproc
|
||||||
import Text.Pandoc.Builder as Pandoc
|
import Text.Pandoc.Builder as Pandoc
|
||||||
import Text.Pandoc.MediaBag (MediaBag)
|
import Text.Pandoc.MediaBag (MediaBag)
|
||||||
import Text.Pandoc.Options
|
import Text.Pandoc.Options
|
||||||
|
@ -464,8 +464,9 @@ parPartToInlines' (Field info children) =
|
||||||
opts <- asks docxOptions
|
opts <- asks docxOptions
|
||||||
if isEnabled Ext_citations opts
|
if isEnabled Ext_citations opts
|
||||||
then do
|
then do
|
||||||
_citation <- readEndNoteXMLCitation (toSources t)
|
citation <- readEndNoteXMLCitation (toSources t)
|
||||||
undefined -- TODO
|
cs <- handleCitation citation
|
||||||
|
return $ cite cs formattedCite
|
||||||
else return formattedCite
|
else return formattedCite
|
||||||
CslCitation t -> do
|
CslCitation t -> do
|
||||||
formattedCite <- smushInlines <$> mapM parPartToInlines' children
|
formattedCite <- smushInlines <$> mapM parPartToInlines' children
|
||||||
|
@ -476,28 +477,7 @@ parPartToInlines' (Field info children) =
|
||||||
case eitherDecode bs of
|
case eitherDecode bs of
|
||||||
Left _err -> return formattedCite
|
Left _err -> return formattedCite
|
||||||
Right citation -> do
|
Right citation -> do
|
||||||
let toPandocCitation item =
|
cs <- handleCitation citation
|
||||||
Citation{ citationId = unItemId (citationItemId item)
|
|
||||||
, citationPrefix = maybe [] (toList . text) $
|
|
||||||
citationItemPrefix item
|
|
||||||
, citationSuffix = (toList . text) $
|
|
||||||
maybe mempty (\x ->
|
|
||||||
fromMaybe "" (citationItemLabel item)
|
|
||||||
<> " " <> x <> " ")
|
|
||||||
(citationItemLocator item)
|
|
||||||
<> fromMaybe mempty (citationItemSuffix item)
|
|
||||||
, citationMode = NormalCitation -- TODO for now
|
|
||||||
, citationNoteNum = 0
|
|
||||||
, citationHash = 0 }
|
|
||||||
let items = citationItems citation
|
|
||||||
let cs = map toPandocCitation items
|
|
||||||
refs <- mapM (traverse (return . text)) $
|
|
||||||
mapMaybe citationItemData items
|
|
||||||
modify $ \st ->
|
|
||||||
st{ docxReferences = foldr
|
|
||||||
(\ref -> M.insert (referenceId ref) ref)
|
|
||||||
(docxReferences st)
|
|
||||||
refs }
|
|
||||||
return $ cite cs formattedCite
|
return $ cite cs formattedCite
|
||||||
else return formattedCite
|
else return formattedCite
|
||||||
CslBibliography -> do
|
CslBibliography -> do
|
||||||
|
@ -508,10 +488,41 @@ parPartToInlines' (Field info children) =
|
||||||
EndNoteRefList -> do
|
EndNoteRefList -> do
|
||||||
opts <- asks docxOptions
|
opts <- asks docxOptions
|
||||||
if isEnabled Ext_citations opts
|
if isEnabled Ext_citations opts
|
||||||
then return mempty -- omit Zotero-generated bibliography
|
then return mempty -- omit EndNote-generated bibliography
|
||||||
else smushInlines <$> mapM parPartToInlines' children
|
else smushInlines <$> mapM parPartToInlines' children
|
||||||
_ -> smushInlines <$> mapM parPartToInlines' children
|
_ -> smushInlines <$> mapM parPartToInlines' children
|
||||||
|
|
||||||
|
-- Turn a 'Citeproc.Citation' into a list of 'Text.Pandoc.Definition.Citation',
|
||||||
|
-- and store the embedded bibliographic data in state.
|
||||||
|
handleCitation :: PandocMonad m
|
||||||
|
=> Citeproc.Citation T.Text
|
||||||
|
-> DocxContext m [Citation]
|
||||||
|
handleCitation citation = do
|
||||||
|
let toPandocCitation item =
|
||||||
|
Citation{ citationId = unItemId (Citeproc.citationItemId item)
|
||||||
|
, citationPrefix = maybe [] (toList . text) $
|
||||||
|
Citeproc.citationItemPrefix item
|
||||||
|
, citationSuffix = (toList . text) $
|
||||||
|
maybe mempty (\x ->
|
||||||
|
fromMaybe "" (Citeproc.citationItemLabel item)
|
||||||
|
<> " " <> x <> " ")
|
||||||
|
(Citeproc.citationItemLocator item)
|
||||||
|
<> fromMaybe mempty (Citeproc.citationItemSuffix item)
|
||||||
|
, citationMode = NormalCitation -- TODO for now
|
||||||
|
, citationNoteNum = 0
|
||||||
|
, citationHash = 0 }
|
||||||
|
let items = Citeproc.citationItems citation
|
||||||
|
let cs = map toPandocCitation items
|
||||||
|
refs <- mapM (traverse (return . text)) $
|
||||||
|
mapMaybe Citeproc.citationItemData items
|
||||||
|
modify $ \st ->
|
||||||
|
st{ docxReferences = foldr
|
||||||
|
(\ref -> M.insert (referenceId ref) ref)
|
||||||
|
(docxReferences st)
|
||||||
|
refs }
|
||||||
|
return cs
|
||||||
|
|
||||||
|
|
||||||
isAnchorSpan :: Inline -> Bool
|
isAnchorSpan :: Inline -> Bool
|
||||||
isAnchorSpan (Span (_, ["anchor"], []) _) = True
|
isAnchorSpan (Span (_, ["anchor"], []) _) = True
|
||||||
isAnchorSpan _ = False
|
isAnchorSpan _ = False
|
||||||
|
|
|
@ -60,11 +60,11 @@ readEndNoteXML :: (PandocMonad m, ToSources a)
|
||||||
=> ReaderOptions -> a -> m Pandoc
|
=> ReaderOptions -> a -> m Pandoc
|
||||||
readEndNoteXML _opts inp = do
|
readEndNoteXML _opts inp = do
|
||||||
let sources = toSources inp
|
let sources = toSources inp
|
||||||
refs <- readEndNoteXMLReferences sources
|
refs <- readEndNoteXMLReferences sources >>= mapM (traverse (return . text))
|
||||||
return $ setMeta "references" (map referenceToMetaValue refs) $ B.doc mempty
|
return $ setMeta "references" (map referenceToMetaValue refs) $ B.doc mempty
|
||||||
|
|
||||||
readEndNoteXMLCitation :: PandocMonad m
|
readEndNoteXMLCitation :: PandocMonad m
|
||||||
=> Sources -> m (Citeproc.Citation Inlines)
|
=> Sources -> m (Citeproc.Citation Text)
|
||||||
readEndNoteXMLCitation sources = do
|
readEndNoteXMLCitation sources = do
|
||||||
tree <- either (throwError . PandocXMLError "") return $
|
tree <- either (throwError . PandocXMLError "") return $
|
||||||
parseXMLElement (TL.fromStrict . sourcesToText $ sources)
|
parseXMLElement (TL.fromStrict . sourcesToText $ sources)
|
||||||
|
@ -78,7 +78,7 @@ readEndNoteXMLCitation sources = do
|
||||||
}
|
}
|
||||||
|
|
||||||
readEndNoteXMLReferences :: PandocMonad m
|
readEndNoteXMLReferences :: PandocMonad m
|
||||||
=> Sources -> m [Reference Inlines]
|
=> Sources -> m [Reference Text]
|
||||||
readEndNoteXMLReferences sources = do
|
readEndNoteXMLReferences sources = do
|
||||||
tree <- either (throwError . PandocXMLError "") return $
|
tree <- either (throwError . PandocXMLError "") return $
|
||||||
parseXMLElement (TL.fromStrict . sourcesToText $ sources)
|
parseXMLElement (TL.fromStrict . sourcesToText $ sources)
|
||||||
|
@ -86,7 +86,7 @@ readEndNoteXMLReferences sources = do
|
||||||
return $ map recordToReference records
|
return $ map recordToReference records
|
||||||
|
|
||||||
|
|
||||||
toCitationItem :: Element -> Citeproc.CitationItem Inlines
|
toCitationItem :: Element -> Citeproc.CitationItem Text
|
||||||
toCitationItem el =
|
toCitationItem el =
|
||||||
Citeproc.CitationItem{ Citeproc.citationItemId =
|
Citeproc.CitationItem{ Citeproc.citationItemId =
|
||||||
maybe mempty referenceId mbref
|
maybe mempty referenceId mbref
|
||||||
|
@ -98,13 +98,12 @@ toCitationItem el =
|
||||||
, Citeproc.citationItemData = mbref
|
, Citeproc.citationItemData = mbref
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
mbref :: Maybe (Reference Inlines)
|
|
||||||
mbref = recordToReference <$> filterChildName (name "record") el
|
mbref = recordToReference <$> filterChildName (name "record") el
|
||||||
|
|
||||||
name :: Text -> (QName -> Bool)
|
name :: Text -> (QName -> Bool)
|
||||||
name t = (== t) . qName
|
name t = (== t) . qName
|
||||||
|
|
||||||
recordToReference :: Element -> Reference Inlines
|
recordToReference :: Element -> Reference Text
|
||||||
recordToReference e =
|
recordToReference e =
|
||||||
Reference{ referenceId = ItemId refid,
|
Reference{ referenceId = ItemId refid,
|
||||||
referenceType = reftype,
|
referenceType = reftype,
|
||||||
|
@ -117,7 +116,6 @@ recordToReference e =
|
||||||
getText' (Elem el) = mconcat $ map getText' $ elContent el
|
getText' (Elem el) = mconcat $ map getText' $ elContent el
|
||||||
getText' (Text cd) = cdData cd
|
getText' (Text cd) = cdData cd
|
||||||
getText' (CRef _) = mempty
|
getText' (CRef _) = mempty
|
||||||
-- mconcat . map cdData . onlyText . elContent
|
|
||||||
refid = maybe mempty (T.strip . strContent)
|
refid = maybe mempty (T.strip . strContent)
|
||||||
(filterElementName (name "key") e
|
(filterElementName (name "key") e
|
||||||
<|> filterElementName (name "rec-number") e)
|
<|> filterElementName (name "rec-number") e)
|
||||||
|
@ -128,30 +126,30 @@ recordToReference e =
|
||||||
filterChildrenName (name "contributors") e >>=
|
filterChildrenName (name "contributors") e >>=
|
||||||
filterChildrenName (name "authors") >>=
|
filterChildrenName (name "authors") >>=
|
||||||
filterChildrenName (name "author") >>=
|
filterChildrenName (name "author") >>=
|
||||||
toName [] . B.toList . B.text . T.strip . getText
|
toName [] . B.toList . B.text . T.strip . getText
|
||||||
titles = do
|
titles = do
|
||||||
x <- filterChildrenName (name "titles") e
|
x <- filterChildrenName (name "titles") e
|
||||||
(key, name') <- [("title", "title"),
|
(key, name') <- [("title", "title"),
|
||||||
("container-title", "secondary-title")]
|
("container-title", "secondary-title")]
|
||||||
(key,) . FancyVal . B.text . T.strip . getText <$>
|
(key,) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name name') x
|
filterChildrenName (name name') x
|
||||||
pages = ("pages",) . FancyVal . B.text. T.strip . getText <$>
|
pages = ("pages",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "pages") e
|
filterChildrenName (name "pages") e
|
||||||
volume = ("volume",) . FancyVal . B.text. T.strip . getText <$>
|
volume = ("volume",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "volume") e
|
filterChildrenName (name "volume") e
|
||||||
number = ("number",) . FancyVal . B.text. T.strip . getText <$>
|
number = ("number",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "number") e
|
filterChildrenName (name "number") e
|
||||||
isbn = ("isbn",) . FancyVal . B.text. T.strip . getText <$>
|
isbn = ("isbn",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "isbn") e
|
filterChildrenName (name "isbn") e
|
||||||
publisher = ("publisher",) . FancyVal . B.text. T.strip . getText <$>
|
publisher = ("publisher",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "publisher") e
|
filterChildrenName (name "publisher") e
|
||||||
originalPublisher =
|
originalPublisher =
|
||||||
("original-publisher",) . FancyVal . B.text. T.strip . getText <$>
|
("original-publisher",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "orig-pub") e
|
filterChildrenName (name "orig-pub") e
|
||||||
publisherPlace =
|
publisherPlace =
|
||||||
("publisher-place",) . FancyVal . B.text. T.strip . getText <$>
|
("publisher-place",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "pub-location") e
|
filterChildrenName (name "pub-location") e
|
||||||
abstract = ("abstract",) . FancyVal . B.text. T.strip . getText <$>
|
abstract = ("abstract",) . FancyVal . T.strip . getText <$>
|
||||||
filterChildrenName (name "abstract") e
|
filterChildrenName (name "abstract") e
|
||||||
dates = ("issued",) . toDate <$> filterChildrenName (name "dates") e
|
dates = ("issued",) . toDate <$> filterChildrenName (name "dates") e
|
||||||
toDate e' = DateVal $
|
toDate e' = DateVal $
|
||||||
|
|
Loading…
Reference in a new issue