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.
This commit is contained in:
parent
b239c89a82
commit
02d3c71e72
6 changed files with 54 additions and 26 deletions
10
data/templates/default.biblatex
Normal file
10
data/templates/default.biblatex
Normal file
|
@ -0,0 +1,10 @@
|
|||
$for(header-includes)$
|
||||
$header-includes$
|
||||
$endfor$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
$endfor$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
$include-after$
|
||||
$endfor$
|
|
@ -56,6 +56,8 @@ data-files:
|
|||
data/templates/default.icml
|
||||
data/templates/default.opml
|
||||
data/templates/default.latex
|
||||
data/templates/default.bibtex
|
||||
data/templates/default.biblatex
|
||||
data/templates/default.context
|
||||
data/templates/default.texinfo
|
||||
data/templates/default.jira
|
||||
|
|
|
@ -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,9 +234,11 @@ 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 <> "}")
|
||||
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
|
||||
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
|
||||
|
|
|
@ -81,8 +81,6 @@ getDefaultTemplate writer = do
|
|||
case format of
|
||||
"native" -> return ""
|
||||
"csljson" -> return ""
|
||||
"bibtex" -> return ""
|
||||
"biblatex" -> return ""
|
||||
"json" -> return ""
|
||||
"docx" -> return ""
|
||||
"fb2" -> return ""
|
||||
|
|
|
@ -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
|
||||
|
||||
|
||||
|
|
|
@ -51,8 +51,8 @@ references:
|
|||
^D
|
||||
@article{garaud,
|
||||
author = {Garaud, Marcel},
|
||||
title = {{Recherches sur les défrichements dans la Gâtine poitevine aux
|
||||
XI\textsuperscript{e} et XII\textsuperscript{e} siècles}},
|
||||
title = {{Recherches sur les défrichements dans la Gâtine poitevine
|
||||
aux XI\textsuperscript{e} et XII\textsuperscript{e} siècles}},
|
||||
journal = {Bulletin de la Société des antiquaires de l’Ouest},
|
||||
series = {4},
|
||||
volume = {9},
|
||||
|
|
Loading…
Reference in a new issue