File: Biblio.hs

package info (click to toggle)
haskell-hakyll 4.16.2.2-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 928 kB
  • sloc: haskell: 6,504; xml: 44; makefile: 9
file content (189 lines) | stat: -rw-r--r-- 8,022 bytes parent folder | download
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
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
--------------------------------------------------------------------------------
-- | 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 'readPandocBiblio'. This function also
-- takes the reader options for completeness -- you can use
-- 'defaultHakyllReaderOptions' if you're unsure. If you already read the
-- source into a 'Pandoc' type and need to add processing for the bibliography,
-- you can use 'processPandocBiblio' instead.
-- 'pandocBiblioCompiler' is a convenience wrapper which works like 'pandocCompiler',
-- but also takes paths to compiled bibliography and csl files;
-- 'pandocBibliosCompiler' is similar but instead takes a glob pattern for bib files.
{-# LANGUAGE Arrows                     #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
module Hakyll.Web.Pandoc.Biblio
    ( CSL (..)
    , cslCompiler
    , Biblio (..)
    , biblioCompiler
    , readPandocBiblio
    , readPandocBiblios
    , processPandocBiblio
    , processPandocBiblios
    , pandocBiblioCompiler
    , pandocBibliosCompiler
    ) where


--------------------------------------------------------------------------------
import           Control.Monad                 (liftM)
import           Data.Binary                   (Binary (..))
import qualified Data.ByteString               as B
import qualified Data.ByteString.Lazy          as BL
import qualified Data.Map                      as Map
import qualified Data.Time                     as Time
import qualified Data.Text                     as T (pack)
import           Data.Typeable                 (Typeable)
import           Hakyll.Core.Compiler
import           Hakyll.Core.Compiler.Internal
import           Hakyll.Core.Identifier
import           Hakyll.Core.Identifier.Pattern (fromGlob)
import           Hakyll.Core.Item
import           Hakyll.Core.Writable
import           Hakyll.Web.Pandoc
import           Text.Pandoc                   (Extension (..), Pandoc,
                                                ReaderOptions (..),
                                                enableExtension)
import qualified Text.Pandoc                   as Pandoc
import qualified Text.Pandoc.Citeproc          as Pandoc (processCitations)
import           System.FilePath               (addExtension, takeExtension)


--------------------------------------------------------------------------------
newtype CSL = CSL {unCSL :: B.ByteString}
    deriving (Binary, Show, Typeable)



--------------------------------------------------------------------------------
instance Writable CSL where
    -- Shouldn't be written.
    write _ _ = return ()


--------------------------------------------------------------------------------
cslCompiler :: Compiler (Item CSL)
cslCompiler = fmap (CSL . BL.toStrict) <$> getResourceLBS


--------------------------------------------------------------------------------
newtype Biblio = Biblio {unBiblio :: B.ByteString}
    deriving (Binary, Show, Typeable)


--------------------------------------------------------------------------------
instance Writable Biblio where
    -- Shouldn't be written.
    write _ _ = return ()


--------------------------------------------------------------------------------
biblioCompiler :: Compiler (Item Biblio)
biblioCompiler = fmap (Biblio . BL.toStrict) <$> getResourceLBS


--------------------------------------------------------------------------------
readPandocBiblio :: ReaderOptions
                 -> Item CSL
                 -> Item Biblio
                 -> (Item String)
                 -> Compiler (Item Pandoc)
readPandocBiblio ropt csl biblio = readPandocBiblios ropt csl [biblio]

readPandocBiblios :: ReaderOptions
                  -> Item CSL
                  -> [Item Biblio]
                  -> (Item String)
                  -> Compiler (Item Pandoc)
readPandocBiblios ropt csl biblios item = do
  pandoc <- readPandocWith ropt item
  processPandocBiblios csl biblios pandoc


--------------------------------------------------------------------------------
processPandocBiblio :: Item CSL
                    -> Item Biblio
                    -> (Item Pandoc)
                    -> Compiler (Item Pandoc)
processPandocBiblio csl biblio = processPandocBiblios csl [biblio]

processPandocBiblios :: Item CSL
                     -> [Item Biblio]
                     -> (Item Pandoc)
                     -> Compiler (Item Pandoc)
processPandocBiblios csl biblios item = do
    -- It's not straightforward to use the Pandoc API as of 2.11 to deal with
    -- citations, since it doesn't export many things in 'Text.Pandoc.Citeproc'.
    -- The 'citeproc' package is also hard to use.
    --
    -- So instead, we try treating Pandoc as a black box.  Pandoc can read
    -- specific csl and bilbio files based on metadata keys.
    --
    -- So we load the CSL and Biblio files and pass them to Pandoc using the
    -- ersatz filesystem.
    let Pandoc.Pandoc (Pandoc.Meta meta) blocks = itemBody item
        cslFile = Pandoc.FileInfo zeroTime . unCSL $ itemBody csl
        bibFiles = zipWith (\x y ->
            ( addExtension ("_hakyll/bibliography-" ++ show x)
                           (takeExtension $ toFilePath $ itemIdentifier y)
            , Pandoc.FileInfo zeroTime . unBiblio . itemBody $ y
            )
          )
          [0 :: Integer ..]
          biblios

        stFiles = foldr ((.) . uncurry Pandoc.insertInFileTree)
                    (Pandoc.insertInFileTree "_hakyll/style.csl" cslFile)
                    bibFiles

        addBiblioFiles = \st -> st { Pandoc.stFiles = stFiles $ Pandoc.stFiles st }

        biblioMeta = Pandoc.Meta .
            Map.insert "csl" (Pandoc.MetaString "_hakyll/style.csl") .
            Map.insert "bibliography"
              (Pandoc.MetaList $ map (Pandoc.MetaString . T.pack . fst) bibFiles) $
            meta
        errOrPandoc = Pandoc.runPure $ do
            Pandoc.modifyPureState addBiblioFiles
            Pandoc.processCitations $ Pandoc.Pandoc biblioMeta blocks

    pandoc <- case errOrPandoc of
        Left  e -> compilerThrow ["Error during processCitations: " ++ show e]
        Right x -> return x

    return $ fmap (const pandoc) item

  where
    zeroTime = Time.UTCTime (toEnum 0) 0


--------------------------------------------------------------------------------
-- | Compiles a markdown file via Pandoc. Requires the .csl and .bib files to be known to the compiler via match statements.
pandocBiblioCompiler :: String -> String -> Compiler (Item String)
pandocBiblioCompiler cslFileName bibFileName = do
    csl <- load $ fromFilePath cslFileName
    bib <- load $ fromFilePath bibFileName
    liftM writePandoc
        (getResourceBody >>= readPandocBiblio ropt csl bib)
    where ropt = defaultHakyllReaderOptions
            { -- The following option enables citation rendering
              readerExtensions = enableExtension Ext_citations $ readerExtensions defaultHakyllReaderOptions
            }

--------------------------------------------------------------------------------
-- | Compiles a markdown file via Pandoc. Requires the .csl and .bib files to be known to the compiler via match statements.
pandocBibliosCompiler :: String -> String -> Compiler (Item String)
pandocBibliosCompiler cslFileName bibFileName = do
    csl  <- load    $ fromFilePath cslFileName
    bibs <- loadAll $ fromGlob bibFileName
    liftM writePandoc
        (getResourceBody >>= readPandocBiblios ropt csl bibs)
    where ropt = defaultHakyllReaderOptions
            { -- The following option enables citation rendering
              readerExtensions = enableExtension Ext_citations $ readerExtensions defaultHakyllReaderOptions
            }