Update to new Pandoc and Hakyll.

This commit is contained in:
Justin Hsu 2018-02-17 18:18:06 +00:00
parent 58491440ce
commit 4ac7538d0c
2 changed files with 27 additions and 19 deletions

View File

@ -1,3 +1,5 @@
module Main where
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid
@ -56,33 +58,33 @@ bib2bibParse file =
--------------------------------------------------------------------------------
main :: IO ()
main = hakyllWith config $ do
match "files/**" $ do
match (fromGlob "files/**") $ do
route idRoute
compile copyFileCompiler
match "images/**" $ do
match (fromGlob "images/**") $ do
route idRoute
compile copyFileCompiler
match "css/*.scss" $ do
match (fromGlob "css/*.scss") $ do
route $ setExtension "css"
compile $ compass
forM_ bibHeaders $ \(nick, flags) ->
create [fromCapture "bibs/*.html" nick] $ do
create [fromCapture (fromGlob "bibs/*.html") nick] $ do
route idRoute
compile $
let biblioCtx = mconcat
[ field "bibitems" $ return . itemBody ] in do
bibTpl <- loadBody "templates/bibitemtpl.html"
bibTpl <- loadBody $ fromFilePath "templates/bibitemtpl.html"
(bib2bib flags)
>>= bib2bibParse
>>= applyTemplateList bibTpl bibEntryContext
>>= makeItem
>>= loadAndApplyTemplate "templates/biblisttpl.html" biblioCtx
>>= loadAndApplyTemplate (fromFilePath "templates/biblisttpl.html") biblioCtx
>>= relativizeUrls
match "content/biblio.md" $ do
match (fromGlob "content/biblio.md") $ do
route $ setExtension "html"
compile $ do
let makeBibCtx (nick, _) =
@ -93,26 +95,26 @@ main = hakyllWith config $ do
>>= applyAsTemplate biblioCtx
>>= relativizeUrls
match "content/*.md" $ do
match (fromGlob "content/*.md") $ do
route $ setExtension "html"
compile $ do
let secDiv = defaultHakyllWriterOptions { writerSectionDivs = True }
pandocCompilerWith defaultHakyllReaderOptions secDiv
>>= relativizeUrls
match "index.html" $ do
match (fromGlob "index.html") $ do
route idRoute
compile $ do
let loadSec sec = field sec
(\_ -> loadBody (fromFilePath $ "content/" ++ sec ++ ".md"))
mainContext = mconcat $ fmap loadSec contentSections
indexContext =
field "footer" (\_ -> loadBody "content/footer.md")
field "footer" (\_ -> loadBody $ fromFilePath "content/footer.md")
`mappend`
defaultContext
getResourceBody
>>= applyAsTemplate mainContext
>>= loadAndApplyTemplate "templates/main.html" indexContext
>>= loadAndApplyTemplate (fromFilePath "templates/main.html") indexContext
>>= relativizeUrls
match "templates/*" $ compile templateCompiler
match (fromGlob "templates/*") $ compile templateCompiler

View File

@ -19,10 +19,11 @@ import Data.Char (isSpace)
import Data.List.Split (splitOn)
import Data.List (intercalate)
import qualified Data.Map as M (empty)
import Data.Text (pack, unpack)
import Data.Typeable (Typeable)
import Hakyll
import qualified Bibtex as B
import qualified Text.Pandoc as Pandoc
import Text.Pandoc
import qualified Text.Parsec as Parsec
--------------------------------------------------------------------------------
@ -128,11 +129,16 @@ trimSpace :: String -> String
trimSpace = f . f
where f = reverse . dropWhile isSpace
-- Remove <p> and </p> tags...
trimPara :: String -> String
trimPara str = concat $ splitOn "</p>" $ drop 3 str
--------------------------------------------------------------------------------
latexToHtml :: String -> String
latexToHtml tex =
let p = case Pandoc.readLaTeX Pandoc.def tex of
Right (Pandoc.Pandoc meta [Pandoc.Para para]) ->
Pandoc.Pandoc meta [Pandoc.Plain para]
Left _ ->
Pandoc.Pandoc (Pandoc.Meta M.empty) []
in Pandoc.writeHtmlString Pandoc.def p
let res = runPure $ readLaTeX def (pack tex)
>>= writeHtml5String def
>>= return . trimPara . unpack
in case res of
Left _ -> ""
Right html -> html