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

73 lines
2.4 KiB
Haskell
Raw Normal View History

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.
--
2011-11-21 19:27:35 +00:00
{-# LANGUAGE Arrows, DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
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
import Control.Applicative ((<$>))
2012-11-09 15:34:45 +00:00
import Control.Arrow (arr, returnA, (>>>))
2011-11-21 19:27:35 +00:00
import Data.Typeable (Typeable)
import Data.Binary (Binary (..))
2011-11-22 07:39:44 +00:00
import Text.Pandoc (Pandoc, ParserState (..))
2011-11-21 19:27:35 +00:00
import Text.Pandoc.Biblio (processBiblio)
import qualified Text.CSL as CSL
import Hakyll.Core.Compiler
import Hakyll.Core.Identifier
import Hakyll.Core.Writable
import Hakyll.Web.Page
2011-11-22 07:39:44 +00:00
import Hakyll.Web.Pandoc
2011-11-21 19:27:35 +00:00
newtype CSL = CSL FilePath
deriving (Binary, Show, Typeable, Writable)
2012-11-09 15:34:45 +00:00
cslCompiler :: Compiler () CSL
cslCompiler = getIdentifier >>> arr (CSL . toFilePath)
2011-11-21 19:27:35 +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)
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-09 15:34:45 +00:00
biblioCompiler :: Compiler () Biblio
biblioCompiler = getIdentifier >>>
arr toFilePath >>> unsafeCompiler CSL.readBiblioFile >>> arr Biblio
2011-11-21 19:27:35 +00:00
2011-11-22 07:39:44 +00:00
pageReadPandocBiblio :: ParserState
-> Identifier CSL
-> Identifier Biblio
-> Compiler (Page String) (Page Pandoc)
pageReadPandocBiblio state csl refs = proc page -> do
2011-11-21 19:27:35 +00:00
CSL csl' <- require_ csl -< ()
2011-11-22 07:39:44 +00:00
Biblio refs' <- require_ refs -< ()
-- 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!
let cits = map CSL.refId refs'
state' = state {stateCitations = stateCitations state ++ cits}
pandocPage <- pageReadPandocWithA -< (state', page)
let pandoc = pageBody pandocPage
2012-02-06 15:04:18 +00:00
pandoc' <- unsafeCompiler processBiblio' -< (csl', refs', pandoc)
2011-11-22 07:39:44 +00:00
returnA -< pandocPage {pageBody = pandoc'}
2011-11-21 19:27:35 +00:00
where
2012-02-06 15:04:18 +00:00
processBiblio' (c, r, p) = processBiblio c Nothing r p