Add links to references

This commit is contained in:
Dimitri Lozeve 2020-03-27 17:42:24 +01:00
parent e051efb407
commit f8065acf1f
5 changed files with 53 additions and 16 deletions

37
site.hs
View file

@ -1,11 +1,17 @@
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Map as Map
import Data.Monoid (mappend)
import qualified Text.CSL as CSL
import Text.CSL.Pandoc (processCites)
import Text.Pandoc
import Text.Pandoc.Options
import Text.Pandoc.Highlighting
import Hakyll
import Hakyll.Core.Compiler.Internal (compilerProvider, compilerAsk)
import Hakyll.Core.Provider (resourceFilePath)
--------------------------------------------------------------------------------
@ -116,6 +122,35 @@ postCtx =
feedCtx :: Context String
feedCtx = postCtx <> bodyField "description"
-- Add links to references ------------------------------------------
-- Source: https://github.com/jaspervdj/hakyll/issues/471#issuecomment-244540329
addLinkCitations (Pandoc meta a) =
let prevMap = unMeta meta
newMap = Map.insert "link-citations" (MetaBool True) prevMap
newMeta = Meta newMap
in Pandoc newMeta a
myReadPandocBiblio :: ReaderOptions
-> Item CSL
-> Item Biblio
-> (Item String)
-> Compiler (Item Pandoc)
myReadPandocBiblio ropt csl biblio item = do
-- Parse CSL file, if given
provider <- compilerProvider <$> compilerAsk
style <- unsafeCompiler $
CSL.readCSLFile Nothing . (resourceFilePath provider) . itemIdentifier $ csl
-- 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 Biblio refs = itemBody biblio
pandoc <- itemBody <$> readPandocWith ropt item
let pandoc' = processCites style refs (addLinkCitations pandoc)
return $ fmap (const pandoc') item
-- Pandoc compiler with KaTeX and bibliography support --------------------
customPandocCompiler :: Compiler (Item String)
customPandocCompiler =
let customExtensions = extensionsFromList [Ext_latex_macros]
@ -130,7 +165,7 @@ customPandocCompiler =
csl <- load $ fromFilePath "csl/chicago-author-date.csl"
bib <- load $ fromFilePath "bib/bibliography.bib"
writePandocWith writerOptions <$>
(getResourceBody >>= readPandocBiblio readerOptions csl bib)
(getResourceBody >>= myReadPandocBiblio readerOptions csl bib)
type FeedRenderer = FeedConfiguration
-> Context String