hakyll/src/Hakyll/Web/Pandoc/Biblio.hs

86 lines
3.1 KiB
Haskell
Raw Normal View History

2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2011-11-21 19:27:35 +00:00
-- | Wraps pandocs bibiliography handling
2011-11-22 07:39:44 +00:00
--
-- In order to add a bibliography, you will need a bibliography file (e.g.
-- @.bib@) and a CSL file (@.csl@). Both need to be compiled with their
-- respective compilers ('biblioCompiler' and 'cslCompiler'). Then, you can
-- refer to these files when you use 'pageReadPandocBiblio'. This function also
-- takes a parser state for completeness -- you can use
-- 'defaultHakyllParserState' if you're unsure.
2012-11-13 16:31:03 +00:00
{-# LANGUAGE Arrows #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2011-11-21 19:27:35 +00:00
module Hakyll.Web.Pandoc.Biblio
( CSL
, cslCompiler
2011-11-22 07:39:44 +00:00
, Biblio (..)
, biblioCompiler
, pageReadPandocBiblio
2011-11-21 19:27:35 +00:00
) where
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2012-11-13 16:31:03 +00:00
import Control.Applicative ((<$>))
import Data.Binary (Binary (..))
import Data.Typeable (Typeable)
import qualified Text.CSL as CSL
import Text.Pandoc (Pandoc, ParserState (..))
import Text.Pandoc.Biblio (processBiblio)
2011-11-21 19:27:35 +00:00
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2012-11-13 16:31:03 +00:00
import Hakyll.Core.Compiler
import Hakyll.Core.Identifier
import Hakyll.Core.Writable
import Hakyll.Web.Page
import Hakyll.Web.Pandoc
2011-11-21 19:27:35 +00:00
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2011-11-21 19:27:35 +00:00
newtype CSL = CSL FilePath
deriving (Binary, Show, Typeable, Writable)
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2012-11-13 16:31:03 +00:00
cslCompiler :: Compiler CSL
cslCompiler = CSL . toFilePath <$> getIdentifier
2011-11-21 19:27:35 +00:00
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2011-11-22 07:39:44 +00:00
newtype Biblio = Biblio [CSL.Reference]
2011-11-21 19:27:35 +00:00
deriving (Show, Typeable)
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2011-11-22 07:39:44 +00:00
instance Binary Biblio where
2011-11-21 19:27:35 +00:00
-- Ugly.
2011-11-22 07:39:44 +00:00
get = Biblio . read <$> get
put (Biblio rs) = put $ show rs
2011-11-21 19:27:35 +00:00
2011-11-22 07:39:44 +00:00
instance Writable Biblio where
2011-11-21 19:27:35 +00:00
write _ _ = return ()
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2012-11-13 16:31:03 +00:00
biblioCompiler :: Compiler Biblio
biblioCompiler = do
filePath <- toFilePath <$> getIdentifier
unsafeCompiler $ Biblio <$> CSL.readBiblioFile filePath
2011-11-21 19:27:35 +00:00
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2011-11-22 07:39:44 +00:00
pageReadPandocBiblio :: ParserState
2012-11-13 16:31:03 +00:00
-> CSL
-> Biblio
-> Page
-> Compiler Pandoc
pageReadPandocBiblio state (CSL csl) (Biblio refs) page = do
2011-11-22 07:39:44 +00:00
-- We need to know the citation keys, add then *before* actually parsing the
-- actual page. If we don't do this, pandoc won't even consider them
-- citations!
2012-11-13 16:31:03 +00:00
let cits = map CSL.refId refs
2011-11-22 07:39:44 +00:00
state' = state {stateCitations = stateCitations state ++ cits}
2012-11-13 16:31:03 +00:00
pandoc <- pageReadPandocWith state' page
pandoc' <- unsafeCompiler $ processBiblio csl Nothing refs pandoc
return pandoc'