diff options
-rw-r--r-- | COPYRIGHT | 11 | ||||
-rw-r--r-- | data/jats.csl | 203 | ||||
-rw-r--r-- | pandoc.cabal | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/App.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/JATS.hs | 33 | ||||
-rw-r--r-- | test/command/7016.md | 48 |
6 files changed, 72 insertions, 241 deletions
@@ -181,7 +181,7 @@ http://github.com/paulrouget/dzslides Released under the Do What the Fuck You Want To Public License. ------------------------------------------------------------------------ -Pandoc embeds a lua interpreter (via hslua). +Pandoc embeds a Lua interpreter (via hslua). Copyright © 1994–2020 Lua.org, PUC-Rio. @@ -203,12 +203,3 @@ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. - ------------------------------------------------------------------------- -The template pandoc.jats is Copyright 2013--2015 Martin Fenner, -released under GPL version 2 or later. - -The file data/jats.csl is derived from a csl file by Martin Fenner, -revised by Martin Paul Eve and then John MacFarlane. -"This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 -License. Originally by Martin Fenner." diff --git a/data/jats.csl b/data/jats.csl deleted file mode 100644 index 6972cb3f8..000000000 --- a/data/jats.csl +++ /dev/null @@ -1,203 +0,0 @@ -<?xml version="1.0" encoding="utf-8"?> -<style xmlns="http://purl.org/net/xbiblio/csl" class="in-text" version="1.0" default-locale="en-US"> - <info> - <title>Journal Article Tag Suite</title> - <title-short>JATS</title-short> - <id>http://www.zotero.org/styles/journal-article-tag-suite</id> - <link href="https://github.com/MartinPaulEve/JATS-CSL/blob/master/jats.csl" rel="self"/> - <link rel="documentation" href="http://jats.nlm.nih.gov/archiving/tag-library/1.0/index.html"/> - <author> - <name>Martin Paul Eve</name> - <email>martin@martineve.com</email> - </author> - <category citation-format="numeric"/> - <category field="medicine"/> - <category field="biology"/> - <summary>Use this style to generate bibliographic data in Journal Article Tagging Suite (JATS) 1.0 XML format</summary> - <updated>2014-06-21T17:41:26+00:00</updated> - <rights license="http://creativecommons.org/licenses/by-sa/3.0/">This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License. Originally by Martin Fenner.</rights> - </info> - <locale xml:lang="en"> - <terms> - <term name="et-al">{{jats}}<etal/>{{/jats}}</term> - </terms> - </locale> - <macro name="citation-number"> - <text variable="citation-number" prefix="{{jats}}id="ref-{{/jats}}" suffix="{{jats}}">{{/jats}}"/> - </macro> - <macro name="author"> - <names variable="author" delimiter=" "> - <name prefix="{{jats}}<name>{{/jats}}" suffix="{{jats}}</name>{{/jats}}" name-as-sort-order="all" sort-separator=" "> - <name-part name="family" text-case="capitalize-first" prefix="{{jats}}<surname>{{/jats}}" suffix="{{jats}}</surname>{{/jats}}"/> - <name-part name="given" text-case="capitalize-first" prefix="{{jats}}<given-names>{{/jats}}" suffix="{{jats}}</given-names>{{/jats}}"/> - </name> - <substitute> - <names variable="editor"/> - </substitute> - </names> - </macro> - - <macro name="editor" delimiter=" "> - <names variable="editor" prefix="{{jats}}<person-group person-group-type="editor">{{/jats}}" suffix="{{jats}}</person-group>{{/jats}}"> - <name prefix="{{jats}}<name>{{/jats}}" suffix="{{jats}}</name>{{/jats}}" name-as-sort-order="all" sort-separator=" "> - <name-part name="family" text-case="capitalize-first" prefix="{{jats}}<surname>{{/jats}}" suffix="{{jats}}</surname>{{/jats}}"/> - <name-part name="given" text-case="capitalize-first" prefix="{{jats}}<given-names>{{/jats}}" suffix="{{jats}}</given-names>{{/jats}}"/> - </name> - <substitute> - <names variable="editor"/> - </substitute> - </names> - </macro> - - <macro name="editor"> - <group delimiter=": "> - <names variable="editor"> - <name prefix="{{jats}}<name>{{/jats}}" suffix="{{jats}}</name>{{/jats}}" name-as-sort-order="all" sort-separator=""> - <name-part name="family" text-case="capitalize-first" prefix="{{jats}}<surname>{{/jats}}" suffix="{{jats}}</surname>{{/jats}}"/> - <name-part name="given" text-case="capitalize-first" prefix="{{jats}}<given-names>{{/jats}}" suffix="{{jats}}<given-names>{{/jats}}"/> - </name> - </names> - </group> - </macro> - <macro name="title"> - <choose> - <if type="book" match="any"> - <group prefix="{{jats}}<source>{{/jats}}" suffix="{{jats}}</source>{{/jats}}"> - <text variable="title"/> - </group> - </if> - <else> - <group prefix="{{jats}}<article-title>{{/jats}}" suffix="{{jats}}</article-title>{{/jats}}"> - <text variable="title"/> - </group> - </else> - </choose> - </macro> - <macro name="container-title"> - <text variable="container-title" form="short" prefix="{{jats}}<source>{{/jats}}" suffix="{{jats}}</source>{{/jats}}"/> - </macro> - <macro name="publisher"> - <text variable="publisher" prefix="{{jats}}<publisher-name>{{/jats}}" suffix="{{jats}}</publisher-name>{{/jats}}"/> - <text variable="publisher-place" prefix="{{jats}}<publisher-loc>{{/jats}}" suffix="{{jats}}</publisher-loc>{{/jats}}"/> - </macro> - <macro name="link"> - <choose> - <if match="any" variable="DOI"> - <group prefix="{{jats}}<pub-id pub-id-type="doi">{{/jats}}" suffix="{{jats}}</pub-id>{{/jats}}"> - <text variable="DOI"/> - </group> - </if> - </choose> - <choose> - <if match="any" variable="PMID"> - <group prefix="{{jats}}<pub-id pub-id-type="pmid">{{/jats}}" suffix="{{jats}}</pub-id>{{/jats}}"> - <text variable="PMID"/> - </group> - </if> - </choose> - <choose> - <if variable="URL" match="any"> - <text variable="URL" /> - </if> - </choose> - </macro> - <macro name="date"> - <choose> - <if type="article-journal article-magazine article-newspaper report patent book" match="any"> - <group prefix="{{jats}}<date>{{/jats}}" suffix="{{jats}}</date>{{/jats}}"> - <date variable="issued"> - <date-part name="day" form="numeric-leading-zeros" prefix="{{jats}}<day>{{/jats}}" suffix="{{jats}}</day>{{/jats}}"/> - <date-part name="month" form="numeric-leading-zeros" prefix="{{jats}}<month>{{/jats}}" suffix="{{jats}}</month>{{/jats}}"/> - <date-part name="year" prefix="{{jats}}<year>{{/jats}}" suffix="{{jats}}</year>{{/jats}}"/> - </date> - </group> - </if> - <else> - <group prefix="{{jats}}<date-in-citation content-type="access-date"{{/jats}}" suffix="{{jats}}</date-in-citation>{{/jats}}"> - <date variable="accessed" prefix="{{jats}} iso-8601-date="{{/jats}}" suffix="{{jats}}">{{/jats}}"> - <date-part name="year"/> - <date-part name="month" form="numeric-leading-zeros" prefix="{{jats}}-{{/jats}}"/> - <date-part name="day" form="numeric-leading-zeros" prefix="{{jats}}-{{/jats}}"/> - </date> - <date variable="accessed"> - <date-part name="day" prefix="{{jats}}<day>{{/jats}}" suffix="{{jats}}</day>{{/jats}}"/> - <date-part name="month" form="numeric-leading-zeros" prefix="{{jats}}<month>{{/jats}}" suffix="{{jats}}</month>{{/jats}}"/> - <date-part name="year" prefix="{{jats}}<year>{{/jats}}" suffix="{{jats}}</year>{{/jats}}"/> - </date> - </group> - </else> - </choose> - </macro> - <macro name="location"> - <choose> - <if type="article-journal article-magazine" match="any"> - <text variable="volume" prefix="{{jats}}<volume>{{/jats}}" suffix="{{jats}}</volume>{{/jats}}"/> - <text variable="issue" prefix="{{jats}}<issue>{{/jats}}" suffix="{{jats}}</issue>{{/jats}}"/> - </if> - </choose> - <choose> - <if type="article-journal article-magazine article-newspaper chapter" match="any"> - <text variable="page-first" prefix="{{jats}}<fpage>{{/jats}}" suffix="{{jats}}</fpage>{{/jats}}"/> - </if> - </choose> - </macro> - <macro name="publication-type"> - <group prefix="{{jats}} publication-type="{{/jats}}" suffix="{{jats}}">{{/jats}}"> - <choose> - <if type="article-journal article-magazine article-newspaper" match="any"> - <text value="journal"/> - </if> - <else-if type="book" match="any"> - <text value="book"/> - </else-if> - <else-if type="chapter" match="any"> - <text value="bookchapter"/> - </else-if> - <else-if type="dataset" match="any"> - <text value="dataset"/> - </else-if> - <else-if type="patent" match="any"> - <text value="patent"/> - </else-if> - <else-if type="report" match="any"> - <text value="report"/> - </else-if> - <else-if type="review" match="any"> - <text value="review"/> - </else-if> - <else> - <text value="standard"/> - </else> - </choose> - </group> - </macro> - <citation collapse="citation-number"> - <sort> - <key variable="citation-number"/> - </sort> - <layout delimiter=","> - <group prefix="{{jats}}<xref ref-type="bibr" rid="{{/jats}}" suffix="{{jats}}</xref>{{/jats}}"> - <text variable="citation-number" prefix="{{jats}}ref-{{/jats}}" suffix="{{jats}}">{{/jats}}"/> - <text variable="citation-number"/> - </group> - </layout> - </citation> - <bibliography sort-separator=""> - <layout> - <group prefix="{{jats}}<ref {{/jats}}" suffix="{{jats}}</ref>{{/jats}}"> - <text macro="citation-number"/> - <group prefix="{{jats}}<element-citation{{/jats}}" suffix="{{jats}}</element-citation>{{/jats}}"> - <text macro="publication-type"/> - <text macro="author" prefix="{{jats}}<person-group person-group-type="author">{{/jats}}" suffix="{{jats}}</person-group>{{/jats}}"/> - <text macro="title" /> - <text macro="container-title"/> - <text macro="editor"/> - <text macro="publisher"/> - <text macro="date"/> - <text macro="location"/> - <text macro="link"/> - </group> - </group> - </layout> - </bibliography> -</style> diff --git a/pandoc.cabal b/pandoc.cabal index ede9af6f0..db8dab491 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -180,8 +180,6 @@ data-files: data/pandoc.List.lua -- bash completion template data/bash_completion.tpl - -- jats csl - data/jats.csl -- citeproc data/default.csl citeproc/biblatex-localization/*.lbx.strings diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 725c76424..437af3257 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -50,10 +50,9 @@ import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts, import Text.Pandoc.App.CommandLineOptions (parseOptions, options) import Text.Pandoc.App.OutputSettings (OutputSettings (..), optToOutputSettings) import Text.Pandoc.BCP47 (Lang (..), parseBCP47) -import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Filter (Filter (JSONFilter, LuaFilter), applyFilters) import Text.Pandoc.PDF (makePDF) -import Text.Pandoc.SelfContained (makeDataURI, makeSelfContained) +import Text.Pandoc.SelfContained (makeSelfContained) import Text.Pandoc.Shared (eastAsianLineBreakFilter, stripEmptyParagraphs, headerShift, isURI, tabFilter, uriPathToPath, filterIpynbOutput, defaultUserDataDirs, tshow, findM) @@ -190,17 +189,6 @@ convertWithOpts opts = do Nothing -> readDataFile "abbreviations" Just f -> readFileStrict f - metadata <- if format == "jats" && - isNothing (lookupMeta "csl" (optMetadata opts)) && - isNothing (lookupMeta "citation-style" - (optMetadata opts)) - then do - jatsCSL <- readDataFile "jats.csl" - let jatsEncoded = makeDataURI - ("application/xml", jatsCSL) - return $ setMeta "csl" jatsEncoded $ optMetadata opts - else return $ optMetadata opts - case lookupMetaString "lang" (optMetadata opts) of "" -> setTranslations $ Lang "en" "" "US" [] l -> case parseBCP47 l of @@ -286,7 +274,7 @@ convertWithOpts opts = do then fillMediaBag else return) >=> return . adjustMetadata (metadataFromFile <>) - >=> return . adjustMetadata (<> metadata) + >=> return . adjustMetadata (<> optMetadata opts) >=> applyTransforms transforms >=> applyFilters readerOpts filters [T.unpack format] >=> maybe return extractMedia (optExtractMedia opts) diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index e8d93b8d5..b2266d179 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.JATS - Copyright : Copyright (C) 2017-2021 John MacFarlane + Copyright : 2017-2021 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane <jgm@berkeley.edu> @@ -168,13 +168,15 @@ plainToPara x = x -- | Convert a list of pairs of terms and definitions into a list of -- JATS varlistentrys. deflistItemsToJATS :: PandocMonad m - => WriterOptions -> [([Inline],[[Block]])] -> JATS m (Doc Text) + => WriterOptions + -> [([Inline],[[Block]])] -> JATS m (Doc Text) deflistItemsToJATS opts items = vcat <$> mapM (uncurry (deflistItemToJATS opts)) items -- | Convert a term and a list of blocks into a JATS varlistentry. deflistItemToJATS :: PandocMonad m - => WriterOptions -> [Inline] -> [[Block]] -> JATS m (Doc Text) + => WriterOptions + -> [Inline] -> [[Block]] -> JATS m (Doc Text) deflistItemToJATS opts term defs = do term' <- inlinesToJATS opts term def' <- wrappedBlocksToJATS (not . isPara) @@ -186,7 +188,8 @@ deflistItemToJATS opts term defs = do -- | Convert a list of lists of blocks to a list of JATS list items. listItemsToJATS :: PandocMonad m - => WriterOptions -> Maybe [Text] -> [[Block]] -> JATS m (Doc Text) + => WriterOptions + -> Maybe [Text] -> [[Block]] -> JATS m (Doc Text) listItemsToJATS opts markers items = case markers of Nothing -> vcat <$> mapM (listItemToJATS opts Nothing) items @@ -194,12 +197,13 @@ listItemsToJATS opts markers items = -- | Convert a list of blocks into a JATS list item. listItemToJATS :: PandocMonad m - => WriterOptions -> Maybe Text -> [Block] -> JATS m (Doc Text) + => WriterOptions + -> Maybe Text -> [Block] -> JATS m (Doc Text) listItemToJATS opts mbmarker item = do contents <- wrappedBlocksToJATS (not . isParaOrList) opts (walk demoteHeaderAndRefs item) return $ inTagsIndented "list-item" $ - maybe empty (\lbl -> inTagsSimple "label" (text $ T.unpack lbl)) mbmarker + maybe empty (inTagsSimple "label" . text . T.unpack) mbmarker $$ contents imageMimeType :: Text -> [(Text, Text)] -> (Text, Text) @@ -247,7 +251,9 @@ blockToJATS opts (Div (id',"section":_,kvs) (Header _lvl _ ils : xs)) = do return $ inTags True "sec" attribs $ inTagsSimple "title" title' $$ contents -- Bibliography reference: -blockToJATS opts (Div (T.stripPrefix "ref-" -> Just _,_,_) [Para lst]) = +blockToJATS opts (Div (ident,_,_) [Para lst]) | "ref-" `T.isPrefixOf` ident = + inTags True "ref" [("id", ident)] . + inTagsSimple "mixed-citation" <$> inlinesToJATS opts lst blockToJATS opts (Div ("refs",_,_) xs) = do contents <- blocksToJATS opts xs @@ -470,10 +476,13 @@ inlineToJATS _ (Link _attr [Str t] (T.stripPrefix "mailto:" -> Just email, _)) | escapeURI t == email = return $ inTagsSimple "email" $ literal (escapeStringForXML email) inlineToJATS opts (Link (ident,_,kvs) txt (T.uncons -> Just ('#', src), _)) = do - let attr = [("id", ident) | not (T.null ident)] ++ - [("alt", stringify txt) | not (null txt)] ++ - [("rid", src)] ++ - [(k,v) | (k,v) <- kvs, k `elem` ["ref-type", "specific-use"]] + let attr = mconcat + [ [("id", ident) | not (T.null ident)] + , [("alt", stringify txt) | not (null txt)] + , [("rid", src)] + , [(k,v) | (k,v) <- kvs, k `elem` ["ref-type", "specific-use"]] + , [("ref-type", "bibr") | "ref-" `T.isPrefixOf` src] + ] if null txt then return $ selfClosingTag "xref" attr else do @@ -529,7 +538,7 @@ demoteHeaderAndRefs (Div ("refs",cls,kvs) bs) = demoteHeaderAndRefs x = x parseDate :: Text -> Maybe Day -parseDate s = msum (map (\fs -> parsetimeWith fs $ T.unpack s) formats) :: Maybe Day +parseDate s = msum (map (`parsetimeWith` T.unpack s) formats) where parsetimeWith = parseTimeM True defaultTimeLocale formats = ["%x","%m/%d/%Y", "%D","%F", "%d %b %Y", "%e %B %Y", "%b. %e, %Y", "%B %e, %Y", diff --git a/test/command/7016.md b/test/command/7016.md new file mode 100644 index 000000000..c2d791ce9 --- /dev/null +++ b/test/command/7016.md @@ -0,0 +1,48 @@ +``` +% pandoc --citeproc --to=jats_archiving --standalone +--- +csl: command/apa.csl +references: +- id: doe + type: article + author: + - family: Doe + given: Jane + container-title: Proceedings of the Academy of Test Inputs + doi: 10.x/nope + issued: 2021 + title: Another article +... +Blah [@doe]. +^D +<?xml version="1.0" encoding="utf-8" ?> +<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Archiving and Interchange DTD v1.2 20190208//EN" + "JATS-archivearticle1.dtd"> +<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.2" article-type="other"> +<front> +<journal-meta> +<journal-id></journal-id> +<journal-title-group> +</journal-title-group> +<issn></issn> +<publisher> +<publisher-name></publisher-name> +</publisher> +</journal-meta> +<article-meta> +</article-meta> +</front> +<body> +<p>Blah (Doe, 2021).</p> +</body> +<back> +<ref-list> + <ref id="ref-doe"> + <mixed-citation>Doe, J. (2021). Another article. <italic>Proceedings + of the Academy of Test Inputs</italic>. + doi:<ext-link ext-link-type="uri" xlink:href="https://doi.org/10.x/nope">10.x/nope</ext-link></mixed-citation> + </ref> +</ref-list> +</back> +</article> +``` |