{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.CslJson
( readCslJson )
where
import Text.Pandoc.Options
import Text.Pandoc.Definition
import Text.Pandoc.Builder (setMeta, cite, str)
import qualified Text.Pandoc.UTF8 as UTF8
import qualified Data.Text as T
import Text.Pandoc.Error (PandocError(..))
import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Citeproc.CslJson (cslJsonToReferences)
import Text.Pandoc.Citeproc.MetaValue (referenceToMetaValue)
import Control.Monad.Except (throwError)
import Text.Pandoc.Sources (ToSources(..), sourcesToText)
readCslJson :: (PandocMonad m, ToSources a)
=> ReaderOptions -> a -> m Pandoc
readCslJson :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readCslJson ReaderOptions
_opts a
x =
case ByteString -> Either String [Reference Inlines]
cslJsonToReferences (Text -> ByteString
UTF8.fromText forall a b. (a -> b) -> a -> b
$ Sources -> Text
sourcesToText forall a b. (a -> b) -> a -> b
$ forall a. ToSources a => a -> Sources
toSources a
x) of
Left String
e -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocParseError forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
e
Right [Reference Inlines]
refs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
setMeta Text
"references"
(forall a b. (a -> b) -> [a] -> [b]
map Reference Inlines -> MetaValue
referenceToMetaValue [Reference Inlines]
refs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
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
"[@*]"))
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
nullMeta []