JATS writer: use either styled-content or named-content for spans.
If the element has a content-type attribute, or at least one class, then that value is used as `content-type` and the span is put inside a `<named-content>` element. Otherwise a `<styled-content>` element is used instead. Closes: #7211
This commit is contained in:
parent
0921b82d98
commit
85f379e474
2 changed files with 35 additions and 15 deletions
|
@ -21,12 +21,13 @@ module Text.Pandoc.Writers.JATS
|
||||||
, writeJatsPublishing
|
, writeJatsPublishing
|
||||||
, writeJatsArticleAuthoring
|
, writeJatsArticleAuthoring
|
||||||
) where
|
) where
|
||||||
|
import Control.Applicative ((<|>))
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Data.Generics (everywhere, mkT)
|
import Data.Generics (everywhere, mkT)
|
||||||
import Data.List (partition)
|
import Data.List (partition)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe, listToMaybe)
|
||||||
import Data.Time (toGregorian, Day, parseTimeM, defaultTimeLocale, formatTime)
|
import Data.Time (toGregorian, Day, parseTimeM, defaultTimeLocale, formatTime)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
@ -449,18 +450,33 @@ inlineToJATS opts (Note contents) = do
|
||||||
$ text (show notenum)
|
$ text (show notenum)
|
||||||
inlineToJATS opts (Cite _ lst) =
|
inlineToJATS opts (Cite _ lst) =
|
||||||
inlinesToJATS opts lst
|
inlinesToJATS opts lst
|
||||||
inlineToJATS opts (Span (ident,_,kvs) ils) = do
|
inlineToJATS opts (Span (ident,classes,kvs) ils) = do
|
||||||
contents <- inlinesToJATS opts ils
|
contents <- inlinesToJATS opts ils
|
||||||
let attr = [("id", escapeNCName ident) | not (T.null ident)] ++
|
let commonAttr = [("id", escapeNCName ident) | not (T.null ident)] ++
|
||||||
[("xml:lang",l) | ("lang",l) <- kvs] ++
|
[("xml:lang",l) | ("lang",l) <- kvs] ++
|
||||||
[(k,v) | (k,v) <- kvs
|
[(k,v) | (k,v) <- kvs, k `elem` ["alt", "specific-use"]]
|
||||||
, k `elem` ["alt", "content-type", "rid", "specific-use",
|
-- A named-content element is a good fit for spans, but requires a
|
||||||
"vocab", "vocab-identifier", "vocab-term",
|
-- content-type attribute to be present. We use either the explicit
|
||||||
"vocab-term-identifier"]]
|
-- attribute or the first class as content type. If neither is
|
||||||
|
-- available, then we fall back to using a @styled-content@ element.
|
||||||
|
let (tag, specificAttr) =
|
||||||
|
case lookup "content-type" kvs <|> listToMaybe classes of
|
||||||
|
Just ct -> ( "named-content"
|
||||||
|
, ("content-type", ct) :
|
||||||
|
[(k, v) | (k, v) <- kvs
|
||||||
|
, k `elem` ["rid", "vocab", "vocab-identifier",
|
||||||
|
"vocab-term", "vocab-term-identifier"]])
|
||||||
|
-- Fall back to styled-content
|
||||||
|
Nothing -> ("styled-content"
|
||||||
|
, [(k, v) | (k,v) <- kvs
|
||||||
|
, k `elem` ["style", "style-type", "style-detail",
|
||||||
|
"toggle"]])
|
||||||
|
let attr = commonAttr ++ specificAttr
|
||||||
|
-- unwrap if wrapping element would have no attributes
|
||||||
return $
|
return $
|
||||||
if null attr
|
if null attr
|
||||||
then contents -- unwrap if no relevant attributes are given
|
then contents
|
||||||
else inTags False "named-content" attr contents
|
else inTags False tag attr contents
|
||||||
inlineToJATS _ (Math t str) = do
|
inlineToJATS _ (Math t str) = do
|
||||||
let addPref (Xml.Attr q v)
|
let addPref (Xml.Attr q v)
|
||||||
| Xml.qName q == "xmlns" = Xml.Attr q{ Xml.qName = "xmlns:mml" } v
|
| Xml.qName q == "xmlns" = Xml.Attr q{ Xml.qName = "xmlns:mml" } v
|
||||||
|
|
|
@ -148,13 +148,17 @@ tests =
|
||||||
spanWith nullAttr "text in span" =?>
|
spanWith nullAttr "text in span" =?>
|
||||||
"<p>text in span</p>"
|
"<p>text in span</p>"
|
||||||
|
|
||||||
, "converted to named-content element" =:
|
, "converted to named-content element if class given" =:
|
||||||
spanWith ("a", ["ignored"], [("alt", "aa")]) "text" =?>
|
spanWith ("a", ["genus-species"], [("alt", "aa")]) "C. elegans" =?>
|
||||||
"<p><named-content id=\"a\" alt=\"aa\">text</named-content></p>"
|
("<p><named-content id=\"a\" alt=\"aa\" content-type=\"genus-species\">"
|
||||||
|
<> "C. elegans</named-content></p>")
|
||||||
|
|
||||||
, "unwrapped if named-content element would have no attributes" =:
|
, "unwrapped if styled-content element would have no attributes" =:
|
||||||
spanWith ("", ["ignored"], [("hidden", "true")]) "text in span" =?>
|
spanWith ("", [], [("hidden", "true")]) "text in span" =?>
|
||||||
"<p>text in span</p>"
|
"<p>text in span</p>"
|
||||||
|
|
||||||
|
, "use content-type attribute if present" =:
|
||||||
|
spanWith ("", [], [("content-type", "species")]) "E. coli" =?>
|
||||||
|
"<p><named-content content-type=\"species\">E. coli</named-content></p>"
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
Loading…
Reference in a new issue