{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.BibTeX
( readBibTeX
, readBibLaTeX
)
where
import Text.Pandoc.Options
import Text.Pandoc.Definition
import Text.Pandoc.Builder (setMeta, cite, str)
import Text.Pandoc.Parsing (fromParsecError)
import Citeproc (Lang(..), parseLang)
import Citeproc.Locale (getLocale)
import Text.Pandoc.Error (PandocError(..))
import Text.Pandoc.Class (PandocMonad, lookupEnv)
import Text.Pandoc.Citeproc.BibTeX as BibTeX
import Text.Pandoc.Citeproc.MetaValue (referenceToMetaValue)
import Text.Pandoc.Sources (ToSources(..))
import Control.Monad.Except (throwError)
readBibTeX :: (PandocMonad m, ToSources a)
=> ReaderOptions -> a -> m Pandoc
readBibTeX :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readBibTeX = Variant -> ReaderOptions -> a -> m Pandoc
forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
Variant -> ReaderOptions -> a -> m Pandoc
readBibTeX' Variant
BibTeX.Bibtex
readBibLaTeX :: (PandocMonad m, ToSources a)
=> ReaderOptions -> a -> m Pandoc
readBibLaTeX :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readBibLaTeX = Variant -> ReaderOptions -> a -> m Pandoc
forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
Variant -> ReaderOptions -> a -> m Pandoc
readBibTeX' Variant
BibTeX.Biblatex
readBibTeX' :: (PandocMonad m, ToSources a)
=> Variant -> ReaderOptions -> a -> m Pandoc
readBibTeX' :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
Variant -> ReaderOptions -> a -> m Pandoc
readBibTeX' Variant
variant ReaderOptions
_opts a
t = do
Maybe Text
mblangEnv <- Text -> m (Maybe Text)
forall (m :: * -> *). PandocMonad m => Text -> m (Maybe Text)
lookupEnv Text
"LANG"
let defaultLang :: Lang
defaultLang = Text
-> Maybe Text
-> Maybe Text
-> [Text]
-> [(Text, [(Text, Text)])]
-> [Text]
-> Lang
Lang Text
"en" Maybe Text
forall a. Maybe a
Nothing (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"US") [] [] []
let lang :: Lang
lang = case Maybe Text
mblangEnv of
Maybe Text
Nothing -> Lang
defaultLang
Just Text
l -> (String -> Lang) -> (Lang -> Lang) -> Either String Lang -> Lang
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Lang -> String -> Lang
forall a b. a -> b -> a
const Lang
defaultLang) Lang -> Lang
forall a. a -> a
id (Either String Lang -> Lang) -> Either String Lang -> Lang
forall a b. (a -> b) -> a -> b
$ Text -> Either String Lang
parseLang Text
l
Locale
locale <- case Lang -> Either CiteprocError Locale
getLocale Lang
lang of
Left CiteprocError
e ->
case Lang -> Either CiteprocError Locale
getLocale (Text
-> Maybe Text
-> Maybe Text
-> [Text]
-> [(Text, [(Text, Text)])]
-> [Text]
-> Lang
Lang Text
"en" Maybe Text
forall a. Maybe a
Nothing (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"US") [] [] []) of
Right Locale
l -> Locale -> m Locale
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Locale
l
Left CiteprocError
_ -> PandocError -> m Locale
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Locale) -> PandocError -> m Locale
forall a b. (a -> b) -> a -> b
$ CiteprocError -> PandocError
PandocCiteprocError CiteprocError
e
Right Locale
l -> Locale -> m Locale
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Locale
l
case Variant
-> Locale
-> (Text -> Bool)
-> a
-> Either ParseError [Reference Inlines]
forall a.
ToSources a =>
Variant
-> Locale
-> (Text -> Bool)
-> a
-> Either ParseError [Reference Inlines]
BibTeX.readBibtexString Variant
variant Locale
locale (Bool -> Text -> Bool
forall a b. a -> b -> a
const Bool
True) a
t of
Left ParseError
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Sources -> ParseError -> PandocError
fromParsecError (a -> Sources
forall a. ToSources a => a -> Sources
toSources a
t) ParseError
e
Right [Reference Inlines]
refs -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> [MetaValue] -> Pandoc -> Pandoc
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Pandoc -> Pandoc
setMeta Text
"references"
((Reference Inlines -> MetaValue)
-> [Reference Inlines] -> [MetaValue]
forall a b. (a -> b) -> [a] -> [b]
map Reference Inlines -> MetaValue
referenceToMetaValue [Reference Inlines]
refs)
(Pandoc -> Pandoc) -> (Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines -> Pandoc -> Pandoc
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Pandoc -> Pandoc
setMeta Text
"nocite"
([Citation] -> Inlines -> Inlines
cite [Citation {citationId :: Text
citationId = Text
"*"
, citationPrefix :: [Inline]
citationPrefix = []
, citationSuffix :: [Inline]
citationSuffix = []
, citationMode :: CitationMode
citationMode = CitationMode
NormalCitation
, citationNoteNum :: Int
citationNoteNum = Int
0
, citationHash :: Int
citationHash = Int
0}]
(Text -> Inlines
str Text
"[@*]"))
(Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
nullMeta []