{-# LANGUAGE Arrows #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Web.Pandoc.Biblio
( CSL
, cslCompiler
, Biblio (..)
, biblioCompiler
, readPandocBiblio
, pandocBiblioCompiler
) where
import Control.Monad (liftM, replicateM)
import Data.Binary (Binary (..))
import Data.Typeable (Typeable)
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Core.Provider
import Hakyll.Core.Writable
import Hakyll.Web.Pandoc
import Hakyll.Web.Pandoc.Binary ()
import qualified Text.CSL as CSL
import Text.CSL.Pandoc (processCites)
import Text.Pandoc (Pandoc, ReaderOptions (..),
enableExtension, Extension (..))
data CSL = CSL
deriving (Show, Typeable)
instance Binary CSL where
put CSL = return ()
get = return CSL
instance Writable CSL where
write _ _ = return ()
cslCompiler :: Compiler (Item CSL)
cslCompiler = makeItem CSL
newtype Biblio = Biblio [CSL.Reference]
deriving (Show, Typeable)
instance Binary Biblio where
get = do
len <- get
Biblio <$> replicateM len get
put (Biblio rs) = put (length rs) >> mapM_ put rs
instance Writable Biblio where
write _ _ = return ()
biblioCompiler :: Compiler (Item Biblio)
biblioCompiler = do
filePath <- getResourceFilePath
makeItem =<< unsafeCompiler (Biblio <$> CSL.readBiblioFile idpred filePath)
where
idpred = const True
readPandocBiblio :: ReaderOptions
-> Item CSL
-> Item Biblio
-> (Item String)
-> Compiler (Item Pandoc)
readPandocBiblio ropt csl biblio item = do
provider <- compilerProvider <$> compilerAsk
style <- unsafeCompiler $
CSL.readCSLFile Nothing . (resourceFilePath provider) . itemIdentifier $ csl
let Biblio refs = itemBody biblio
pandoc <- itemBody <$> readPandocWith ropt item
let pandoc' = processCites style refs pandoc
return $ fmap (const pandoc') item
pandocBiblioCompiler :: String -> String -> Compiler (Item String)
pandocBiblioCompiler cslFileName bibFileName = do
csl <- load $ fromFilePath cslFileName
bib <- load $ fromFilePath bibFileName
liftM writePandoc
(getResourceBody >>= readPandocBiblio ropt csl bib)
where ropt = defaultHakyllReaderOptions
{
readerExtensions = enableExtension Ext_citations $ readerExtensions defaultHakyllReaderOptions
}