summaryrefslogtreecommitdiff
path: root/src/Hakyll/Web/Pandoc/Biblio.hs
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2012-11-13 17:31:03 +0100
committerJasper Van der Jeugt <m@jaspervdj.be>2012-11-13 17:31:03 +0100
commitf0af2a3b79ea7eea3f521f79fd903f9023ec85df (patch)
treebbc460b65ab52879c616dffce1bb32fe8d8df2ac /src/Hakyll/Web/Pandoc/Biblio.hs
parentd2e913f42434841c584b97ae9d5417ff2737c0ce (diff)
downloadhakyll-f0af2a3b79ea7eea3f521f79fd903f9023ec85df.tar.gz
WIP
Diffstat (limited to 'src/Hakyll/Web/Pandoc/Biblio.hs')
-rw-r--r--src/Hakyll/Web/Pandoc/Biblio.hs59
1 files changed, 29 insertions, 30 deletions
diff --git a/src/Hakyll/Web/Pandoc/Biblio.hs b/src/Hakyll/Web/Pandoc/Biblio.hs
index 699ba31..ca8d10e 100644
--- a/src/Hakyll/Web/Pandoc/Biblio.hs
+++ b/src/Hakyll/Web/Pandoc/Biblio.hs
@@ -7,7 +7,9 @@
-- 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 #-}
+{-# LANGUAGE Arrows #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Web.Pandoc.Biblio
( CSL
, cslCompiler
@@ -18,21 +20,20 @@ module Hakyll.Web.Pandoc.Biblio
--------------------------------------------------------------------------------
-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 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)
--------------------------------------------------------------------------------
-import Hakyll.Core.Compiler
-import Hakyll.Core.Identifier
-import Hakyll.Core.Writable
-import Hakyll.Web.Page
-import Hakyll.Web.Pandoc
+import Hakyll.Core.Compiler
+import Hakyll.Core.Identifier
+import Hakyll.Core.Writable
+import Hakyll.Web.Page
+import Hakyll.Web.Pandoc
--------------------------------------------------------------------------------
@@ -41,8 +42,8 @@ newtype CSL = CSL FilePath
--------------------------------------------------------------------------------
-cslCompiler :: Compiler () CSL
-cslCompiler = getIdentifier >>> arr (CSL . toFilePath)
+cslCompiler :: Compiler CSL
+cslCompiler = CSL . toFilePath <$> getIdentifier
--------------------------------------------------------------------------------
@@ -61,26 +62,24 @@ instance Writable Biblio where
--------------------------------------------------------------------------------
-biblioCompiler :: Compiler () Biblio
-biblioCompiler = getIdentifier >>>
- arr toFilePath >>> unsafeCompiler CSL.readBiblioFile >>> arr Biblio
+biblioCompiler :: Compiler Biblio
+biblioCompiler = do
+ filePath <- toFilePath <$> getIdentifier
+ unsafeCompiler $ Biblio <$> CSL.readBiblioFile filePath
--------------------------------------------------------------------------------
pageReadPandocBiblio :: ParserState
- -> Identifier CSL
- -> Identifier Biblio
- -> Compiler Page Pandoc
-pageReadPandocBiblio state csl refs = proc page -> do
- CSL csl' <- require_ csl -< ()
- Biblio refs' <- require_ refs -< ()
+ -> CSL
+ -> Biblio
+ -> Page
+ -> Compiler Pandoc
+pageReadPandocBiblio state (CSL csl) (Biblio refs) page = do
-- 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'
+ let cits = map CSL.refId refs
state' = state {stateCitations = stateCitations state ++ cits}
- pandoc <- pageReadPandocWithA -< (state', page)
- pandoc' <- unsafeCompiler processBiblio' -< (csl', refs', pandoc)
- returnA -< pandoc'
- where
- processBiblio' (c, r, p) = processBiblio c Nothing r p
+ pandoc <- pageReadPandocWith state' page
+ pandoc' <- unsafeCompiler $ processBiblio csl Nothing refs pandoc
+ return pandoc'