{-# LANGUAGE TupleSections #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.EndNote
( readEndNoteXML
, readEndNoteXMLCitation
)
where
import Text.Pandoc.Options
import Text.Pandoc.Definition
import Citeproc (Reference(..), ItemId(..), Val(..), Date(..), DateParts(..))
import qualified Citeproc
import Text.Pandoc.Builder as B
import Text.Pandoc.Error (PandocError(..))
import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Citeproc.MetaValue (referenceToMetaValue)
import Text.Pandoc.Sources (Sources(..), ToSources(..), sourcesToText)
import Text.Pandoc.Citeproc.Name (toName, NameOpts(..))
import Control.Applicative ((<|>))
import Control.Monad.Except (throwError)
import Control.Monad (mzero, unless)
import Text.Pandoc.XML.Light
( filterElementName,
strContent,
QName(qName),
Element(..),
Content(..),
CData(..),
filterElementsName,
filterChildName,
filterChildrenName,
findAttrBy,
parseXMLElement )
import qualified Data.Text.Lazy as TL
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.Map as M
import Safe (readMay)
readEndNoteXML :: (PandocMonad m, ToSources a)
=> ReaderOptions -> a -> m Pandoc
readEndNoteXML :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readEndNoteXML ReaderOptions
_opts a
inp = do
let sources :: Sources
sources = forall a. ToSources a => a -> Sources
toSources a
inp
[Reference Inlines]
refs <- forall (m :: * -> *).
PandocMonad m =>
Sources -> m [Reference Text]
readEndNoteXMLReferences Sources
sources forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
text))
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
setMeta Text
"nocite" ([Citation] -> Inlines -> Inlines
cite [Citation {citationId :: Text
citationId = Text
"*"
, citationPrefix :: [Inline]
citationPrefix = []
, citationSuffix :: [Inline]
citationSuffix = []
, citationMode :: CitationMode
citationMode = CitationMode
NormalCitation
, citationNoteNum :: Int
citationNoteNum = Int
0
, citationHash :: Int
citationHash = Int
0}] (Text -> Inlines
str Text
"[@*]")) forall a b. (a -> b) -> a -> b
$
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
setMeta Text
"references" (forall a b. (a -> b) -> [a] -> [b]
map Reference Inlines -> MetaValue
referenceToMetaValue [Reference Inlines]
refs) forall a b. (a -> b) -> a -> b
$
Blocks -> Pandoc
B.doc forall a. Monoid a => a
mempty
readEndNoteXMLCitation :: PandocMonad m
=> Sources -> m (Citeproc.Citation Text)
readEndNoteXMLCitation :: forall (m :: * -> *). PandocMonad m => Sources -> m (Citation Text)
readEndNoteXMLCitation Sources
sources = do
Element
tree <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> PandocError
PandocXMLError Text
"EndNote references") forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
Text -> Either Text Element
parseXMLElement (Text -> Text
TL.fromStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sources -> Text
sourcesToText forall a b. (a -> b) -> a -> b
$ Sources
sources)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (QName -> Text
qName (Element -> QName
elName Element
tree) forall a. Eq a => a -> a -> Bool
== Text
"EndNote") forall a b. (a -> b) -> a -> b
$
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall a b. (a -> b) -> a -> b
$ Text -> Text -> PandocError
PandocXMLError Text
"EndNote references" Text
"Expected EndNote element"
let items :: [CitationItem Text]
items = forall a b. (a -> b) -> [a] -> [b]
map Element -> CitationItem Text
toCitationItem forall a b. (a -> b) -> a -> b
$ (QName -> Bool) -> Element -> [Element]
filterElementsName (Text -> QName -> Bool
name Text
"Cite") Element
tree
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Citeproc.Citation{
citationId :: Maybe Text
Citeproc.citationId = forall a. Maybe a
Nothing
, citationNoteNumber :: Maybe Int
Citeproc.citationNoteNumber = forall a. Maybe a
Nothing
, citationItems :: [CitationItem Text]
Citeproc.citationItems = [CitationItem Text]
items
}
readEndNoteXMLReferences :: PandocMonad m
=> Sources -> m [Reference Text]
readEndNoteXMLReferences :: forall (m :: * -> *).
PandocMonad m =>
Sources -> m [Reference Text]
readEndNoteXMLReferences Sources
sources = do
Element
tree <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> PandocError
PandocXMLError Text
"EndNote references") forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
Text -> Either Text Element
parseXMLElement (Text -> Text
TL.fromStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sources -> Text
sourcesToText forall a b. (a -> b) -> a -> b
$ Sources
sources)
let records :: [Element]
records = (QName -> Bool) -> Element -> [Element]
filterElementsName (Text -> QName -> Bool
name Text
"record") Element
tree
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Element -> Reference Text
recordToReference [Element]
records
toCitationItem :: Element -> Citeproc.CitationItem Text
toCitationItem :: Element -> CitationItem Text
toCitationItem Element
el =
Citeproc.CitationItem{ citationItemId :: ItemId
Citeproc.citationItemId =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty forall a. Reference a -> ItemId
referenceId Maybe (Reference Text)
mbref
, citationItemLabel :: Maybe Text
Citeproc.citationItemLabel = forall a. Maybe a
Nothing
, citationItemLocator :: Maybe Text
Citeproc.citationItemLocator = Maybe Text
mbpages
, citationItemType :: CitationItemType
Citeproc.citationItemType = CitationItemType
Citeproc.NormalCite
, citationItemPrefix :: Maybe Text
Citeproc.citationItemPrefix = Maybe Text
mbprefix
, citationItemSuffix :: Maybe Text
Citeproc.citationItemSuffix = Maybe Text
mbsuffix
, citationItemData :: Maybe (Reference Text)
Citeproc.citationItemData = Maybe (Reference Text)
mbref
}
where
mbref :: Maybe (Reference Text)
mbref = Element -> Reference Text
recordToReference forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (QName -> Bool) -> Element -> Maybe Element
filterChildName (Text -> QName -> Bool
name Text
"record") Element
el
mbprefix :: Maybe Text
mbprefix = Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (QName -> Bool) -> Element -> Maybe Element
filterChildName (Text -> QName -> Bool
name Text
"Prefix") Element
el
mbsuffix :: Maybe Text
mbsuffix = Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (QName -> Bool) -> Element -> Maybe Element
filterChildName (Text -> QName -> Bool
name Text
"Suffix") Element
el
mbpages :: Maybe Text
mbpages = Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (QName -> Bool) -> Element -> Maybe Element
filterChildName (Text -> QName -> Bool
name Text
"Pages") Element
el
name :: Text -> (QName -> Bool)
name :: Text -> QName -> Bool
name Text
t = (forall a. Eq a => a -> a -> Bool
== Text
t) forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName
getText :: Element -> Text
getText :: Element -> Text
getText Element
el = Content -> Text
getText' (Element -> Content
Elem Element
el)
where
getText' :: Content -> Text
getText' (Elem Element
el') = forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Content -> Text
getText' forall a b. (a -> b) -> a -> b
$ Element -> [Content]
elContent Element
el'
getText' (Text CData
cd) = CData -> Text
cdData CData
cd
getText' (CRef Text
_) = forall a. Monoid a => a
mempty
recordToReference :: Element -> Reference Text
recordToReference :: Element -> Reference Text
recordToReference Element
e =
Reference{ referenceId :: ItemId
referenceId = Text -> ItemId
ItemId Text
refid,
referenceType :: Text
referenceType = Text
reftype,
referenceDisambiguation :: Maybe DisambiguationData
referenceDisambiguation = forall a. Maybe a
Nothing,
referenceVariables :: Map Variable (Val Text)
referenceVariables = Map Variable (Val Text)
refvars }
where
refid :: Text
refid = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
strContent)
((QName -> Bool) -> Element -> Maybe Element
filterElementName (Text -> QName -> Bool
name Text
"key") Element
e
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (QName -> Bool) -> Element -> Maybe Element
filterElementName (Text -> QName -> Bool
name Text
"rec-number") Element
e)
reftype :: Text
reftype = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"document" Text -> Text
toCslReferenceType
((QName -> Bool) -> Element -> Maybe Element
filterElementName (Text -> QName -> Bool
name Text
"ref-type") Element
e forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(QName -> Bool) -> Element -> Maybe Text
findAttrBy (Text -> QName -> Bool
name Text
"name"))
authors :: [Name]
authors =
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"contributors") Element
e forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"authors") forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"author") forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
forall (m :: * -> *). Monad m => NameOpts -> [Inline] -> m Name
toName NameOpts{ nameOptsPrefixIsNonDroppingParticle :: Bool
nameOptsPrefixIsNonDroppingParticle = Bool
False
, nameOptsUseJuniorComma :: Bool
nameOptsUseJuniorComma = Bool
False }
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Many a -> [a]
B.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText
titles :: [(Variable, Val Text)]
titles = do
Element
x <- (QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"titles") Element
e
(Variable
key, Text
name') <- [(Variable
"title", Text
"title"),
(Variable
"container-title", Text
"secondary-title")]
(Variable
key,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
name') Element
x
pages :: [(Variable, Val Text)]
pages = (Variable
"pages",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"pages") Element
e
volume :: [(Variable, Val Text)]
volume = (Variable
"volume",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"volume") Element
e
number :: [(Variable, Val Text)]
number = (Variable
"number",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"number") Element
e
isbn :: [(Variable, Val Text)]
isbn = (Variable
"isbn",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"isbn") Element
e
publisher :: [(Variable, Val Text)]
publisher = (Variable
"publisher",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"publisher") Element
e
originalPublisher :: [(Variable, Val Text)]
originalPublisher =
(Variable
"original-publisher",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"orig-pub") Element
e
publisherPlace :: [(Variable, Val Text)]
publisherPlace =
(Variable
"publisher-place",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"pub-location") Element
e
abstract :: [(Variable, Val Text)]
abstract = (Variable
"abstract",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Val a
FancyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"abstract") Element
e
dates :: [(Variable, Val a)]
dates = (Variable
"issued",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. Element -> Val a
toDate forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"dates") Element
e
toDate :: Element -> Val a
toDate Element
e' = forall a. Date -> Val a
DateVal forall a b. (a -> b) -> a -> b
$
Date { dateParts :: [DateParts]
dateParts = Element -> [DateParts]
toDateParts Element
e'
, dateCirca :: Bool
dateCirca = Bool
False
, dateSeason :: Maybe Int
dateSeason = forall a. Maybe a
Nothing
, dateLiteral :: Maybe Text
dateLiteral = forall a. Maybe a
Nothing }
toDateParts :: Element -> [DateParts]
toDateParts Element
e' = do
Element
x <- (QName -> Bool) -> Element -> [Element]
filterChildrenName (Text -> QName -> Bool
name Text
"year") Element
e'
case forall a. Read a => String -> Maybe a
readMay forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
getText forall a b. (a -> b) -> a -> b
$ Element
x of
Maybe Int
Nothing -> forall (m :: * -> *) a. MonadPlus m => m a
mzero
Just Int
y -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y]
refvars :: Map Variable (Val Text)
refvars = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$
[ (Variable
"author", forall a. [Name] -> Val a
NamesVal [Name]
authors) | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Name]
authors) ] forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
titles forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
pages forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
volume forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
number forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
isbn forall a. [a] -> [a] -> [a]
++
forall {a}. [(Variable, Val a)]
dates forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
publisher forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
originalPublisher forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
publisherPlace forall a. [a] -> [a] -> [a]
++
[(Variable, Val Text)]
abstract
toCslReferenceType :: Text -> Text
toCslReferenceType :: Text -> Text
toCslReferenceType Text
t =
case Text
t of
Text
"Aggregated Database" -> Text
"dataset"
Text
"Ancient Text" -> Text
"classic"
Text
"Artwork" -> Text
"graphic"
Text
"Audiovisual Material" -> Text
"graphic"
Text
"Bill" -> Text
"legislation"
Text
"Blog" -> Text
"post-weblog"
Text
"Book" -> Text
"book"
Text
"Book Section" -> Text
"chapter"
Text
"Case" -> Text
"legal_case"
Text
"Catalog" -> Text
"document"
Text
"Chart or Table" -> Text
"graphic"
Text
"Classical Work" -> Text
"classic"
Text
"Computer program" -> Text
"software"
Text
"Conference Paper" -> Text
"article"
Text
"Conference Proceedings" -> Text
"periodical"
Text
"Dataset" -> Text
"dataset"
Text
"Dictionary" -> Text
"book"
Text
"Edited Book" -> Text
"book"
Text
"Electronic Article" -> Text
"article"
Text
"Electronic Book" -> Text
"book"
Text
"Electronic Book Section" -> Text
"chapter"
Text
"Encyclopedia" -> Text
"book"
Text
"Equation" -> Text
"document"
Text
"Figure" -> Text
"graphic"
Text
"Film or Broadcast" -> Text
"motion_picture"
Text
"Government Document" -> Text
"document"
Text
"Grant" -> Text
"document"
Text
"Hearing" -> Text
"hearing"
Text
"Interview" -> Text
"interview"
Text
"Journal Article" -> Text
"article-journal"
Text
"Legal Rule or Regulation" -> Text
"regulation"
Text
"Magazine Article" -> Text
"article-magazine"
Text
"Manuscript" -> Text
"manuscript"
Text
"Map" -> Text
"map"
Text
"Music" -> Text
"musical_score"
Text
"Newspaper Article" -> Text
"article-newspaper"
Text
"Online Database" -> Text
"dataset"
Text
"Online Multimedia" -> Text
"webpage"
Text
"Pamphlet" -> Text
"pamphlet"
Text
"Patent" -> Text
"patent"
Text
"Personal Communication" -> Text
"personal_communication"
Text
"Podcast" -> Text
"document"
Text
"Press Release" -> Text
"report"
Text
"Report" -> Text
"report"
Text
"Serial" -> Text
"periodical"
Text
"Standard" -> Text
"standard"
Text
"Statute" -> Text
"legislation"
Text
"Thesis" -> Text
"thesis"
Text
"Unpublished Work" -> Text
"unpublished"
Text
"Web Page" -> Text
"webpage"
Text
_ -> Text
"document"