{-# LANGUAGE Arrows #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Web.Pandoc.Biblio
( CSL (..)
, cslCompiler
, Biblio (..)
, biblioCompiler
, readPandocBiblio
, processPandocBiblio
, pandocBiblioCompiler
) where
import Control.Monad (liftM)
import Data.Binary (Binary (..))
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Map as Map
import qualified Data.Time as Time
import Data.Typeable (Typeable)
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Core.Writable
import Hakyll.Web.Pandoc
import Text.Pandoc (Extension (..), Pandoc,
ReaderOptions (..),
enableExtension)
import qualified Text.Pandoc as Pandoc
import qualified Text.Pandoc.Citeproc as Pandoc (processCitations)
newtype CSL = CSL {CSL -> ByteString
unCSL :: B.ByteString}
deriving (Get CSL
[CSL] -> Put
CSL -> Put
(CSL -> Put) -> Get CSL -> ([CSL] -> Put) -> Binary CSL
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [CSL] -> Put
$cputList :: [CSL] -> Put
get :: Get CSL
$cget :: Get CSL
put :: CSL -> Put
$cput :: CSL -> Put
Binary, Int -> CSL -> ShowS
[CSL] -> ShowS
CSL -> String
(Int -> CSL -> ShowS)
-> (CSL -> String) -> ([CSL] -> ShowS) -> Show CSL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CSL] -> ShowS
$cshowList :: [CSL] -> ShowS
show :: CSL -> String
$cshow :: CSL -> String
showsPrec :: Int -> CSL -> ShowS
$cshowsPrec :: Int -> CSL -> ShowS
Show, Typeable)
instance Writable CSL where
write :: String -> Item CSL -> IO ()
write String
_ Item CSL
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
cslCompiler :: Compiler (Item CSL)
cslCompiler :: Compiler (Item CSL)
cslCompiler = (ByteString -> CSL) -> Item ByteString -> Item CSL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> CSL
CSL (ByteString -> CSL)
-> (ByteString -> ByteString) -> ByteString -> CSL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.toStrict) (Item ByteString -> Item CSL)
-> Compiler (Item ByteString) -> Compiler (Item CSL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler (Item ByteString)
getResourceLBS
newtype Biblio = Biblio {Biblio -> ByteString
unBiblio :: B.ByteString}
deriving (Get Biblio
[Biblio] -> Put
Biblio -> Put
(Biblio -> Put) -> Get Biblio -> ([Biblio] -> Put) -> Binary Biblio
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Biblio] -> Put
$cputList :: [Biblio] -> Put
get :: Get Biblio
$cget :: Get Biblio
put :: Biblio -> Put
$cput :: Biblio -> Put
Binary, Int -> Biblio -> ShowS
[Biblio] -> ShowS
Biblio -> String
(Int -> Biblio -> ShowS)
-> (Biblio -> String) -> ([Biblio] -> ShowS) -> Show Biblio
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Biblio] -> ShowS
$cshowList :: [Biblio] -> ShowS
show :: Biblio -> String
$cshow :: Biblio -> String
showsPrec :: Int -> Biblio -> ShowS
$cshowsPrec :: Int -> Biblio -> ShowS
Show, Typeable)
instance Writable Biblio where
write :: String -> Item Biblio -> IO ()
write String
_ Item Biblio
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
biblioCompiler :: Compiler (Item Biblio)
biblioCompiler :: Compiler (Item Biblio)
biblioCompiler = (ByteString -> Biblio) -> Item ByteString -> Item Biblio
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> Biblio
Biblio (ByteString -> Biblio)
-> (ByteString -> ByteString) -> ByteString -> Biblio
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.toStrict) (Item ByteString -> Item Biblio)
-> Compiler (Item ByteString) -> Compiler (Item Biblio)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler (Item ByteString)
getResourceLBS
readPandocBiblio :: ReaderOptions
-> Item CSL
-> Item Biblio
-> (Item String)
-> Compiler (Item Pandoc)
readPandocBiblio :: ReaderOptions
-> Item CSL -> Item Biblio -> Item String -> Compiler (Item Pandoc)
readPandocBiblio ReaderOptions
ropt Item CSL
csl Item Biblio
biblio Item String
item = do
Item Pandoc
pandoc <- ReaderOptions -> Item String -> Compiler (Item Pandoc)
readPandocWith ReaderOptions
ropt Item String
item
Item CSL -> Item Biblio -> Item Pandoc -> Compiler (Item Pandoc)
processPandocBiblio Item CSL
csl Item Biblio
biblio Item Pandoc
pandoc
processPandocBiblio :: Item CSL
-> Item Biblio
-> (Item Pandoc)
-> Compiler (Item Pandoc)
processPandocBiblio :: Item CSL -> Item Biblio -> Item Pandoc -> Compiler (Item Pandoc)
processPandocBiblio Item CSL
csl Item Biblio
biblio Item Pandoc
item = do
let Pandoc.Pandoc (Pandoc.Meta Map Text MetaValue
meta) [Block]
blocks = Item Pandoc -> Pandoc
forall a. Item a -> a
itemBody Item Pandoc
item
cslFile :: FileInfo
cslFile = UTCTime -> ByteString -> FileInfo
Pandoc.FileInfo UTCTime
zeroTime (ByteString -> FileInfo) -> (CSL -> ByteString) -> CSL -> FileInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSL -> ByteString
unCSL (CSL -> FileInfo) -> CSL -> FileInfo
forall a b. (a -> b) -> a -> b
$ Item CSL -> CSL
forall a. Item a -> a
itemBody Item CSL
csl
bibFile :: FileInfo
bibFile = UTCTime -> ByteString -> FileInfo
Pandoc.FileInfo UTCTime
zeroTime (ByteString -> FileInfo)
-> (Biblio -> ByteString) -> Biblio -> FileInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Biblio -> ByteString
unBiblio (Biblio -> FileInfo) -> Biblio -> FileInfo
forall a b. (a -> b) -> a -> b
$ Item Biblio -> Biblio
forall a. Item a -> a
itemBody Item Biblio
biblio
addBiblioFiles :: PureState -> PureState
addBiblioFiles = \PureState
st -> PureState
st
{ stFiles :: FileTree
Pandoc.stFiles =
String -> FileInfo -> FileTree -> FileTree
Pandoc.insertInFileTree String
"_hakyll/style.csl" FileInfo
cslFile (FileTree -> FileTree)
-> (FileTree -> FileTree) -> FileTree -> FileTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> FileInfo -> FileTree -> FileTree
Pandoc.insertInFileTree String
"_hakyll/refs.bib" FileInfo
bibFile (FileTree -> FileTree) -> FileTree -> FileTree
forall a b. (a -> b) -> a -> b
$
PureState -> FileTree
Pandoc.stFiles PureState
st
}
biblioMeta :: Meta
biblioMeta = Map Text MetaValue -> Meta
Pandoc.Meta (Map Text MetaValue -> Meta)
-> (Map Text MetaValue -> Map Text MetaValue)
-> Map Text MetaValue
-> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> MetaValue -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Text
"csl" (Text -> MetaValue
Pandoc.MetaString Text
"_hakyll/style.csl") (Map Text MetaValue -> Map Text MetaValue)
-> (Map Text MetaValue -> Map Text MetaValue)
-> Map Text MetaValue
-> Map Text MetaValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> MetaValue -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Text
"bibliography" (Text -> MetaValue
Pandoc.MetaString Text
"_hakyll/refs.bib") (Map Text MetaValue -> Meta) -> Map Text MetaValue -> Meta
forall a b. (a -> b) -> a -> b
$
Map Text MetaValue
meta
errOrPandoc :: Either PandocError Pandoc
errOrPandoc = PandocPure Pandoc -> Either PandocError Pandoc
forall a. PandocPure a -> Either PandocError a
Pandoc.runPure (PandocPure Pandoc -> Either PandocError Pandoc)
-> PandocPure Pandoc -> Either PandocError Pandoc
forall a b. (a -> b) -> a -> b
$ do
(PureState -> PureState) -> PandocPure ()
Pandoc.modifyPureState PureState -> PureState
addBiblioFiles
Pandoc -> PandocPure Pandoc
forall (m :: * -> *). PandocMonad m => Pandoc -> m Pandoc
Pandoc.processCitations (Pandoc -> PandocPure Pandoc) -> Pandoc -> PandocPure Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc.Pandoc Meta
biblioMeta [Block]
blocks
Pandoc
pandoc <- case Either PandocError Pandoc
errOrPandoc of
Left PandocError
e -> [String] -> Compiler Pandoc
forall a. [String] -> Compiler a
compilerThrow [String
"Error during processCitations: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PandocError -> String
forall a. Show a => a -> String
show PandocError
e]
Right Pandoc
x -> Pandoc -> Compiler Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
x
Item Pandoc -> Compiler (Item Pandoc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Item Pandoc -> Compiler (Item Pandoc))
-> Item Pandoc -> Compiler (Item Pandoc)
forall a b. (a -> b) -> a -> b
$ (Pandoc -> Pandoc) -> Item Pandoc -> Item Pandoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Pandoc -> Pandoc -> Pandoc
forall a b. a -> b -> a
const Pandoc
pandoc) Item Pandoc
item
where
zeroTime :: UTCTime
zeroTime = Day -> DiffTime -> UTCTime
Time.UTCTime (Int -> Day
forall a. Enum a => Int -> a
toEnum Int
0) DiffTime
0
pandocBiblioCompiler :: String -> String -> Compiler (Item String)
pandocBiblioCompiler :: String -> String -> Compiler (Item String)
pandocBiblioCompiler String
cslFileName String
bibFileName = do
Item CSL
csl <- Identifier -> Compiler (Item CSL)
forall a. (Binary a, Typeable a) => Identifier -> Compiler (Item a)
load (Identifier -> Compiler (Item CSL))
-> Identifier -> Compiler (Item CSL)
forall a b. (a -> b) -> a -> b
$ String -> Identifier
fromFilePath String
cslFileName
Item Biblio
bib <- Identifier -> Compiler (Item Biblio)
forall a. (Binary a, Typeable a) => Identifier -> Compiler (Item a)
load (Identifier -> Compiler (Item Biblio))
-> Identifier -> Compiler (Item Biblio)
forall a b. (a -> b) -> a -> b
$ String -> Identifier
fromFilePath String
bibFileName
(Item Pandoc -> Item String)
-> Compiler (Item Pandoc) -> Compiler (Item String)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Item Pandoc -> Item String
writePandoc
(Compiler (Item String)
getResourceBody Compiler (Item String)
-> (Item String -> Compiler (Item Pandoc))
-> Compiler (Item Pandoc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ReaderOptions
-> Item CSL -> Item Biblio -> Item String -> Compiler (Item Pandoc)
readPandocBiblio ReaderOptions
ropt Item CSL
csl Item Biblio
bib)
where ropt :: ReaderOptions
ropt = ReaderOptions
defaultHakyllReaderOptions
{
readerExtensions :: Extensions
readerExtensions = Extension -> Extensions -> Extensions
enableExtension Extension
Ext_citations (Extensions -> Extensions) -> Extensions -> Extensions
forall a b. (a -> b) -> a -> b
$ ReaderOptions -> Extensions
readerExtensions ReaderOptions
defaultHakyllReaderOptions
}