{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Readers.CslJson
   Copyright   : Copyright (C) 2020-2021 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Parses CSL JSON bibliographies into a Pandoc document
with empty body and `references` and `nocite` fields
in the metadata.  A wildcard `nocite` is used so that
if the document is rendered in another format, the
entire bibliography will be printed.

<https://citeproc-js.readthedocs.io/en/latest/csl-json/markup.html>.
-}
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)

-- | Read CSL JSON from an input string and return a Pandoc document.
-- The document will have only metadata, with an empty body.
-- The metadata will contain a `references` field with the
-- bibliography entries, and a `nocite` field with the wildcard `[@*]`.
readCslJson :: (PandocMonad m, ToSources a)
            => ReaderOptions -> a -> m Pandoc
readCslJson :: ReaderOptions -> a -> m Pandoc
readCslJson ReaderOptions
_opts a
x =
  case ByteString -> Either String [Reference Inlines]
cslJsonToReferences (Text -> ByteString
UTF8.fromText (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Sources -> Text
sourcesToText (Sources -> Text) -> Sources -> Text
forall a b. (a -> b) -> a -> b
$ a -> Sources
forall a. ToSources a => a -> Sources
toSources a
x) of
    Left String
e -> PandocError -> m Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocParseError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
e
    Right [Reference Inlines]
refs -> Pandoc -> m Pandoc
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
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
setMeta Text
"nocite"
                            ([Citation] -> Inlines -> Inlines
cite [Citation :: Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
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 []