aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-02-01 18:02:17 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2021-02-01 18:05:20 -0800
commit02d3c71e7224853ecabaa9ac4cd947ec2ac1e579 (patch)
treeb311c690e48cd067bfdf236e0357ca73d4d5f6e7 /src/Text/Pandoc
parentb239c89a82b66abc55bf7c08e37492938c817c56 (diff)
downloadpandoc-02d3c71e7224853ecabaa9ac4cd947ec2ac1e579.tar.gz
BibTeX writer: use doclayout and doctemplate.
This change allows bibtex/biblatex output to wrap as other formats do, depending on the settings of `--wrap` and `--columns`. It also introduces default templates for bibtex and biblatex, which allow for using the variables `header-include`, `include-before` or `include-after` (or alternatively the command line options `--include-in-header`, `--include-before-body`, `--include-after-body`) to insert content into the generated bibtex/biblatex. This change requires a change in the return type of the unexported `T.P.Citeproc.writeBibTeXString` from `Text` to `Doc Text`. Closes #7068.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Citeproc/BibTeX.hs41
-rw-r--r--src/Text/Pandoc/Templates.hs2
-rw-r--r--src/Text/Pandoc/Writers/BibTeX.hs19
3 files changed, 39 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Citeproc/BibTeX.hs b/src/Text/Pandoc/Citeproc/BibTeX.hs
index 2b43fffb6..416fe439e 100644
--- a/src/Text/Pandoc/Citeproc/BibTeX.hs
+++ b/src/Text/Pandoc/Citeproc/BibTeX.hs
@@ -52,6 +52,8 @@ import Data.Char (isAlphaNum, isDigit, isLetter,
import Data.List (foldl', intercalate, intersperse)
import Safe (readMay)
import Text.Printf (printf)
+import Text.DocLayout (literal, hsep, nest, hang, Doc(..),
+ braces, ($$), cr)
data Variant = Bibtex | Biblatex
deriving (Show, Eq, Ord)
@@ -77,10 +79,11 @@ writeBibtexString :: WriterOptions -- ^ options (for writing LaTex)
-> Variant -- ^ bibtex or biblatex
-> Maybe Lang -- ^ Language
-> Reference Inlines -- ^ Reference to write
- -> Text
+ -> Doc Text
writeBibtexString opts variant mblang ref =
- "@" <> bibtexType <> "{" <> unItemId (referenceId ref) <> ",\n " <>
- renderFields fs <> "\n}\n"
+ "@" <> bibtexType <> "{" <> literal (unItemId (referenceId ref)) <> ","
+ $$ nest 2 (renderFields fs)
+ $$ "}" <> cr
where
bibtexType =
@@ -231,10 +234,12 @@ writeBibtexString opts variant mblang ref =
toLaTeX x =
case runPure (writeLaTeX opts $ doc (B.plain x)) of
Left _ -> Nothing
- Right t -> Just t
+ Right t -> Just $ hsep . map literal $ T.words t
- renderField name = (\contents -> name <> " = {" <> contents <> "}")
- <$> getContentsFor name
+ renderField :: Text -> Maybe (Doc Text)
+ renderField name =
+ (((literal name) <>) . hang 2 " = " . braces)
+ <$> getContentsFor name
getVariable v = lookupVariable (toVariable v) ref
@@ -248,10 +253,10 @@ writeBibtexString opts variant mblang ref =
Nothing ->
case dateParts date of
[DateParts (y1:_), DateParts (y2:_)] ->
- Just (T.pack (printf "%04d" y1) <> "--" <>
+ Just $ literal (T.pack (printf "%04d" y1) <> "--" <>
T.pack (printf "%04d" y2))
[DateParts (y1:_)] ->
- Just (T.pack (printf "%04d" y1))
+ Just $ literal (T.pack (printf "%04d" y1))
_ -> Nothing
_ -> Nothing
@@ -274,19 +279,19 @@ writeBibtexString opts variant mblang ref =
DateVal date ->
case dateParts date of
[DateParts (_:m1:_), DateParts (_:m2:_)] ->
- Just (toMonth m1 <> "--" <> toMonth m2)
- [DateParts (_:m1:_)] -> Just (toMonth m1)
+ Just $ literal (toMonth m1 <> "--" <> toMonth m2)
+ [DateParts (_:m1:_)] -> Just $ literal (toMonth m1)
_ -> Nothing
_ -> Nothing
- getContentsFor :: Text -> Maybe Text
+ getContentsFor :: Text -> Maybe (Doc Text)
getContentsFor "type" =
getVariableAsText "genre" >>=
\case
"mathesis" -> Just "mastersthesis"
"phdthesis" -> Just "phdthesis"
_ -> Nothing
- getContentsFor "entrysubtype" = mbSubtype
+ getContentsFor "entrysubtype" = literal <$> mbSubtype
getContentsFor "journal"
| bibtexType `elem` ["article", "periodical", "suppperiodical", "review"]
= getVariable "container-title" >>= toLaTeX . valToInlines
@@ -314,7 +319,7 @@ writeBibtexString opts variant mblang ref =
getContentsFor x = getVariable x >>=
if isURL x
- then Just . stringify . valToInlines
+ then Just . literal . stringify . valToInlines
else toLaTeX .
(if x == "title"
then titlecase
@@ -323,7 +328,7 @@ writeBibtexString opts variant mblang ref =
isURL x = x `elem` ["url","doi","issn","isbn"]
- renderFields = T.intercalate ",\n " . mapMaybe renderField
+ renderFields = mconcat . intersperse ("," <> cr) . mapMaybe renderField
defaultLang :: Lang
defaultLang = Lang "en" (Just "US")
@@ -1038,14 +1043,14 @@ getOldDate prefix = do
let dateparts = filter (\x -> x /= DateParts [])
$ map toDateParts [(year',month',day'),
(endyear',endmonth',endday')]
- literal <- if null dateparts
- then Just <$> getRawField (prefix <> "year")
- else return Nothing
+ literal' <- if null dateparts
+ then Just <$> getRawField (prefix <> "year")
+ else return Nothing
return $
Date { dateParts = dateparts
, dateCirca = False
, dateSeason = Nothing
- , dateLiteral = literal }
+ , dateLiteral = literal' }
getRawField :: Text -> Bib Text
getRawField f = do
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 3e539bff7..e83f26329 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -81,8 +81,6 @@ getDefaultTemplate writer = do
case format of
"native" -> return ""
"csljson" -> return ""
- "bibtex" -> return ""
- "biblatex" -> return ""
"json" -> return ""
"docx" -> return ""
"fb2" -> return ""
diff --git a/src/Text/Pandoc/Writers/BibTeX.hs b/src/Text/Pandoc/Writers/BibTeX.hs
index e1cb47ca1..b9ae0c13a 100644
--- a/src/Text/Pandoc/Writers/BibTeX.hs
+++ b/src/Text/Pandoc/Writers/BibTeX.hs
@@ -25,7 +25,11 @@ import Citeproc (parseLang)
import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Citeproc.BibTeX as BibTeX
import Text.Pandoc.Citeproc.MetaValue (metaValueToReference)
-import Text.Pandoc.Writers.Shared (lookupMetaString)
+import Text.Pandoc.Writers.Shared (lookupMetaString, defField,
+ addVariablesToContext)
+import Text.DocLayout (render, vcat)
+import Text.DocTemplates (Context(..))
+import Text.Pandoc.Templates (renderTemplate)
-- | Write BibTeX based on the references metadata from a Pandoc document.
writeBibTeX :: PandocMonad m => WriterOptions -> Pandoc -> m Text
@@ -43,6 +47,15 @@ writeBibTeX' variant opts (Pandoc meta _) = do
let refs = case lookupMeta "references" meta of
Just (MetaList xs) -> mapMaybe metaValueToReference xs
_ -> []
- return $ mconcat $
- map (BibTeX.writeBibtexString opts variant mblang) refs
+ let main = vcat $ map (BibTeX.writeBibtexString opts variant mblang) refs
+ let context = defField "body" main
+ $ addVariablesToContext opts (mempty :: Context Text)
+ let colwidth = if writerWrapText opts == WrapAuto
+ then Just $ writerColumns opts
+ else Nothing
+ return $ render colwidth $
+ case writerTemplate opts of
+ Nothing -> main
+ Just tpl -> renderTemplate tpl context
+