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

107 lines
3.7 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
2013-01-20 08:35:39 +00:00
-- takes the reader options for completeness -- you can use
-- 'defaultHakyllReaderOptions' 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
2012-11-18 20:56:52 +00:00
, readPandocBiblio
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 (..))
2013-01-20 08:35:39 +00:00
import Data.Traversable (traverse)
2012-11-13 16:31:03 +00:00
import Data.Typeable (Typeable)
import qualified Text.CSL as CSL
2013-01-20 08:35:39 +00:00
import Text.Pandoc (Pandoc, ReaderOptions (..))
2012-11-13 16:31:03 +00:00
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
2012-11-18 20:56:52 +00:00
import Hakyll.Core.Item
2012-11-13 16:31:03 +00:00
import Hakyll.Core.Writable
import Hakyll.Web.Pandoc
2011-11-21 19:27:35 +00:00
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2012-11-18 20:56:52 +00:00
data CSL = CSL
deriving (Show, Typeable)
--------------------------------------------------------------------------------
instance Binary CSL where
put CSL = return ()
get = return CSL
--------------------------------------------------------------------------------
instance Writable CSL where
-- Shouldn't be written.
write _ _ = return ()
2011-11-21 19:27:35 +00:00
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2012-11-18 20:56:52 +00:00
cslCompiler :: Compiler (Item CSL)
cslCompiler = makeItem CSL
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
2012-11-18 20:56:52 +00:00
--------------------------------------------------------------------------------
2011-11-22 07:39:44 +00:00
instance Writable Biblio where
2012-11-18 20:56:52 +00:00
-- Shouldn't be written.
2011-11-21 19:27:35 +00:00
write _ _ = return ()
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2012-11-18 20:56:52 +00:00
biblioCompiler :: Compiler (Item Biblio)
2012-11-13 16:31:03 +00:00
biblioCompiler = do
2012-11-18 20:56:52 +00:00
filePath <- toFilePath <$> getUnderlying
makeItem =<< unsafeCompiler (Biblio <$> CSL.readBiblioFile filePath)
2011-11-21 19:27:35 +00:00
2012-11-10 17:11:46 +00:00
--------------------------------------------------------------------------------
2013-01-20 08:35:39 +00:00
readPandocBiblio :: ReaderOptions
-> Maybe (Item CSL)
2012-11-18 20:56:52 +00:00
-> Item Biblio
-> (Item String)
-> Compiler (Item Pandoc)
2013-01-20 08:35:39 +00:00
readPandocBiblio ropt csl biblio item = do
-- Parse CSL file, if given
style <- unsafeCompiler $
traverse (CSL.readCSLFile . toFilePath . itemIdentifier) csl
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-18 20:56:52 +00:00
let Biblio refs = itemBody biblio
2013-01-20 08:35:39 +00:00
ropt' = ropt {readerReferences = readerReferences ropt ++ refs}
pandoc = itemBody $ readPandocWith ropt' item
pandoc' = processBiblio style refs pandoc
2012-11-18 20:56:52 +00:00
return $ fmap (const pandoc') item