summaryrefslogtreecommitdiff
path: root/src/Hakyll/Web/Pandoc/Biblio.hs
blob: 699ba316b174ca54b31984ecb8244a39944d519b (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
--------------------------------------------------------------------------------
-- | Wraps pandocs bibiliography handling
--
-- 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.
{-# LANGUAGE Arrows, DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Hakyll.Web.Pandoc.Biblio
    ( CSL
    , cslCompiler
    , Biblio (..)
    , biblioCompiler
    , 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
    put (Biblio rs) = put $ show rs

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 Pandoc
pageReadPandocBiblio state csl refs = proc page -> do
    CSL csl' <- require_ csl -< ()
    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}
    pandoc  <- pageReadPandocWithA -< (state', page)
    pandoc' <- unsafeCompiler processBiblio' -< (csl', refs', pandoc)
    returnA -< pandoc'
  where
    processBiblio' (c, r, p) = processBiblio c Nothing r p