aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Citeproc.hs43
-rw-r--r--src/Text/Pandoc/Citeproc/CslJson.hs1
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs12
3 files changed, 13 insertions, 43 deletions
diff --git a/src/Text/Pandoc/Citeproc.hs b/src/Text/Pandoc/Citeproc.hs
index 39760776d..9a649402e 100644
--- a/src/Text/Pandoc/Citeproc.hs
+++ b/src/Text/Pandoc/Citeproc.hs
@@ -73,7 +73,9 @@ processCitations (Pandoc meta bs) = do
let linkCites = maybe False truish $ lookupMeta "link-citations" meta
- let opts = defaultCiteprocOptions{ linkCitations = linkCites }
+ let linkBib = maybe True truish $ lookupMeta "link-bibliography" meta
+ let opts = defaultCiteprocOptions{ linkCitations = linkCites
+ , linkBibliography = linkBib }
let result = Citeproc.citeproc opts style mblang refs citations
mapM_ (report . CiteprocWarning) (resultWarnings result)
let sopts = styleOptions style
@@ -105,8 +107,7 @@ processCitations (Pandoc meta bs) = do
$ cits
return $ walk removeQuoteSpan
$ Pandoc meta''
- $ insertRefs refkvs classes meta''
- (walk fixLinks $ B.toList bibs) bs'
+ $ insertRefs refkvs classes meta'' (B.toList bibs) bs'
removeQuoteSpan :: Inline -> Inline
removeQuoteSpan (Span ("",["csl-quoted"],[]) xs) = Span nullAttr xs
@@ -210,7 +211,7 @@ getReferences mblocale (Pandoc meta bs) = do
Nothing -> return []
let addQuoteSpan (Quoted _ xs) = Span ("",["csl-quoted"],[]) xs
addQuoteSpan x = x
- return $ map (linkifyVariables . legacyDateRanges . walk addQuoteSpan)
+ return $ map (legacyDateRanges . walk addQuoteSpan)
(externalRefs ++ inlineRefs)
-- note that inlineRefs can override externalRefs
@@ -278,7 +279,7 @@ insertResolvedCitations (Cite cs ils) = do
[] -> return (Cite cs ils)
(x:xs) -> do
put xs
- return $ Cite cs (walk fixLinks $ B.toList x)
+ return $ Cite cs (B.toList x)
insertResolvedCitations x = return x
getCitations :: Locale
@@ -419,15 +420,6 @@ mvPunct moveNotes locale (Cite cs ils : Str "." : ys)
mvPunct moveNotes locale (x:xs) = x : mvPunct moveNotes locale xs
mvPunct _ _ [] = []
--- move https://doi.org etc. prefix inside link text (#6723):
-fixLinks :: [Inline] -> [Inline]
-fixLinks (Str t : Link attr [Str u1] (u2,tit) : xs)
- | u2 == t <> u1
- = Link attr [Str (t <> u1)] (u2,tit) : fixLinks xs
-fixLinks (x:xs) = x : fixLinks xs
-fixLinks [] = []
-
-
endWithPunct :: Bool -> [Inline] -> Bool
endWithPunct _ [] = False
endWithPunct onlyFinal xs@(_:_) =
@@ -523,29 +515,6 @@ legacyDateRanges ref =
_ -> DateVal d
go x = x
-linkifyVariables :: Reference Inlines -> Reference Inlines
-linkifyVariables ref =
- ref{ referenceVariables = M.mapWithKey go $ referenceVariables ref }
- where
- go "URL" x = tolink "https://" x
- go "DOI" x = tolink "https://doi.org/" (fixShortDOI x)
- go "ISBN" x = tolink "https://worldcat.org/isbn/" x
- go "PMID" x = tolink "https://www.ncbi.nlm.nih.gov/pubmed/" x
- go "PMCID" x = tolink "https://www.ncbi.nlm.nih.gov/pmc/articles/" x
- go _ x = x
- fixShortDOI x = let x' = extractText x
- in if "10/" `T.isPrefixOf` x'
- then TextVal $ T.drop 3 x'
- -- see https://shortdoi.org
- else TextVal x'
- tolink pref x = let x' = extractText x
- x'' = if "://" `T.isInfixOf` x'
- then x'
- else pref <> x'
- in if T.null x'
- then x
- else FancyVal (B.link x'' "" (B.str x'))
-
extractText :: Val Inlines -> Text
extractText (TextVal x) = x
extractText (FancyVal x) = toText x
diff --git a/src/Text/Pandoc/Citeproc/CslJson.hs b/src/Text/Pandoc/Citeproc/CslJson.hs
index 862af5188..43c1a87ec 100644
--- a/src/Text/Pandoc/Citeproc/CslJson.hs
+++ b/src/Text/Pandoc/Citeproc/CslJson.hs
@@ -28,6 +28,7 @@ fromCslJson (CslSub x) = B.subscript (fromCslJson x)
fromCslJson (CslSup x) = B.superscript (fromCslJson x)
fromCslJson (CslNoCase x) = B.spanWith ("",["nocase"],[]) (fromCslJson x)
fromCslJson (CslDiv t x) = B.spanWith ("",["csl-" <> t],[]) (fromCslJson x)
+fromCslJson (CslLink u x) = B.link u "" (fromCslJson x)
cslJsonToReferences :: ByteString -> Either String [Reference Inlines]
cslJsonToReferences raw =
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index feb1c08f5..e0eb72161 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -54,7 +54,7 @@ import System.FilePath.Glob
import Text.DocTemplates (FromContext(lookupContext), Context)
import Text.DocLayout (literal)
import Text.TeXMath
-import Text.Pandoc.Logging (LogMessage(TemplateWarning))
+import Text.Pandoc.Logging (LogMessage(PowerpointTemplateWarning))
import Text.Pandoc.Writers.Math (convertMath)
import Text.Pandoc.Writers.Powerpoint.Presentation
import Text.Pandoc.Shared (tshow, stringify)
@@ -457,11 +457,11 @@ presentationToArchive opts meta pres = do
<> "reference doc or in the default "
<> "reference doc included with pandoc."))
(Nothing, Just ((element, path, entry) :| _)) -> do
- P.logOutput (PowerpointTemplateWarning
- ("Couldn't find layout named \""
- <> layoutTitle <> "\" in provided "
- <> "reference doc. Falling back to "
- <> "the default included with pandoc."))
+ P.report (PowerpointTemplateWarning
+ ("Couldn't find layout named \""
+ <> layoutTitle <> "\" in provided "
+ <> "reference doc. Falling back to "
+ <> "the default included with pandoc."))
pure SlideLayout { slElement = element
, slPath = path
, slEntry = entry