summaryrefslogtreecommitdiff
path: root/src/Hakyll/Web/Pandoc/Biblio.hs
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2012-11-10 18:11:46 +0100
committerJasper Van der Jeugt <m@jaspervdj.be>2012-11-10 18:11:46 +0100
commit141e761ce11d4d4ae9e9b86201249dbd549e2924 (patch)
tree0d0ba398331bceb9326c58392680fb81361fb6c3 /src/Hakyll/Web/Pandoc/Biblio.hs
parent260e4e2e8936f756d2f3a2e6e788f05ca28e4324 (diff)
downloadhakyll-141e761ce11d4d4ae9e9b86201249dbd549e2924.tar.gz
Deprecate things, basics now work
Diffstat (limited to 'src/Hakyll/Web/Pandoc/Biblio.hs')
-rw-r--r--src/Hakyll/Web/Pandoc/Biblio.hs26
1 files changed, 20 insertions, 6 deletions
diff --git a/src/Hakyll/Web/Pandoc/Biblio.hs b/src/Hakyll/Web/Pandoc/Biblio.hs
index 64a702b..699ba31 100644
--- a/src/Hakyll/Web/Pandoc/Biblio.hs
+++ b/src/Hakyll/Web/Pandoc/Biblio.hs
@@ -1,3 +1,4 @@
+--------------------------------------------------------------------------------
-- | Wraps pandocs bibiliography handling
--
-- In order to add a bibliography, you will need a bibliography file (e.g.
@@ -6,7 +7,6 @@
-- 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.
---
{-# LANGUAGE Arrows, DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Hakyll.Web.Pandoc.Biblio
( CSL
@@ -16,30 +16,41 @@ module Hakyll.Web.Pandoc.Biblio
, pageReadPandocBiblio
) where
+
+--------------------------------------------------------------------------------
import Control.Applicative ((<$>))
import Control.Arrow (arr, returnA, (>>>))
import Data.Typeable (Typeable)
-
import Data.Binary (Binary (..))
import Text.Pandoc (Pandoc, ParserState (..))
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
import Hakyll.Web.Pandoc
+
+--------------------------------------------------------------------------------
newtype CSL = CSL FilePath
deriving (Binary, Show, Typeable, Writable)
+
+--------------------------------------------------------------------------------
cslCompiler :: Compiler () CSL
cslCompiler = getIdentifier >>> arr (CSL . toFilePath)
+
+--------------------------------------------------------------------------------
newtype Biblio = Biblio [CSL.Reference]
deriving (Show, Typeable)
+
+--------------------------------------------------------------------------------
instance Binary Biblio where
-- Ugly.
get = Biblio . read <$> get
@@ -48,14 +59,18 @@ instance Binary Biblio where
instance Writable Biblio where
write _ _ = return ()
+
+--------------------------------------------------------------------------------
biblioCompiler :: Compiler () Biblio
biblioCompiler = getIdentifier >>>
arr toFilePath >>> unsafeCompiler CSL.readBiblioFile >>> arr Biblio
+
+--------------------------------------------------------------------------------
pageReadPandocBiblio :: ParserState
-> Identifier CSL
-> Identifier Biblio
- -> Compiler (Page String) (Page Pandoc)
+ -> Compiler Page Pandoc
pageReadPandocBiblio state csl refs = proc page -> do
CSL csl' <- require_ csl -< ()
Biblio refs' <- require_ refs -< ()
@@ -64,9 +79,8 @@ pageReadPandocBiblio state csl refs = proc page -> do
-- citations!
let cits = map CSL.refId refs'
state' = state {stateCitations = stateCitations state ++ cits}
- pandocPage <- pageReadPandocWithA -< (state', page)
- let pandoc = pageBody pandocPage
+ pandoc <- pageReadPandocWithA -< (state', page)
pandoc' <- unsafeCompiler processBiblio' -< (csl', refs', pandoc)
- returnA -< pandocPage {pageBody = pandoc'}
+ returnA -< pandoc'
where
processBiblio' (c, r, p) = processBiblio c Nothing r p