aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-01-11 00:35:48 +0100
committerGitHub <noreply@github.com>2021-01-10 15:35:48 -0800
commit68fa43799963fff11a980d5d3959184c3d34a723 (patch)
tree2d698480fb87219ebef15159e385cadf73e7574b /src/Text
parenta41cb09afec620a826c0636f03a7b77d3d295111 (diff)
downloadpandoc-68fa43799963fff11a980d5d3959184c3d34a723.tar.gz
JATS writer: fix citations (#7018)
* JATS writer: keep code lines at 80 chars or below * JATS writer: fix citations
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/App.hs16
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs33
2 files changed, 23 insertions, 26 deletions
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",