Format site.hs with ormolu
This commit is contained in:
parent
0c47bd7ad1
commit
0800c06188
1 changed files with 80 additions and 75 deletions
83
site.hs
83
site.hs
|
@ -1,17 +1,15 @@
|
|||
--------------------------------------------------------------------------------
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
import qualified Data.Map as Map
|
||||
import Data.Monoid (mappend)
|
||||
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Highlighting
|
||||
import Text.Pandoc.SideNote
|
||||
|
||||
import Hakyll
|
||||
import Hakyll.Core.Compiler.Internal (compilerProvider, compilerAsk)
|
||||
import Hakyll.Core.Compiler.Internal (compilerAsk, compilerProvider)
|
||||
import Hakyll.Core.Provider (resourceFilePath)
|
||||
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Highlighting
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.SideNote
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
main :: IO ()
|
||||
|
@ -47,7 +45,8 @@ main = hakyll $ do
|
|||
route idRoute
|
||||
compile $ do
|
||||
posts <- recentFirst =<< loadAll pattern
|
||||
let ctx = constField "title" title
|
||||
let ctx =
|
||||
constField "title" title
|
||||
<> listField "posts" (postCtxWithTags tags) (return posts)
|
||||
<> defaultContext
|
||||
|
||||
|
@ -58,7 +57,8 @@ main = hakyll $ do
|
|||
|
||||
match "posts/*" $ do
|
||||
route $ setExtension "html"
|
||||
compile $ do
|
||||
compile $
|
||||
do
|
||||
underlying <- getUnderlying
|
||||
toc <- getMetadataField underlying "toc"
|
||||
customPandocCompiler (toc == Just "yes" || toc == Just "true")
|
||||
|
@ -70,7 +70,8 @@ main = hakyll $ do
|
|||
|
||||
match (fromList ["contact.org", "cv.org", "skills.org", "projects.org"]) $ do
|
||||
route $ setExtension "html"
|
||||
compile $ customPandocCompiler False
|
||||
compile $
|
||||
customPandocCompiler False
|
||||
>>= return . fmap demoteHeaders
|
||||
>>= loadAndApplyTemplate "templates/post.html" postCtx
|
||||
>>= loadAndApplyTemplate "templates/default.html" defaultContext
|
||||
|
@ -81,9 +82,9 @@ main = hakyll $ do
|
|||
compile $ do
|
||||
posts <- recentFirst =<< loadAll "posts/*"
|
||||
let archiveCtx =
|
||||
listField "posts" postCtx (return posts) `mappend`
|
||||
constField "title" "Archives" `mappend`
|
||||
defaultContext
|
||||
listField "posts" postCtx (return posts)
|
||||
`mappend` constField "title" "Archives"
|
||||
`mappend` defaultContext
|
||||
makeItem ""
|
||||
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
|
||||
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
|
||||
|
@ -102,8 +103,8 @@ main = hakyll $ do
|
|||
compile $ do
|
||||
posts <- fmap (take 10) $ recentFirst =<< loadAll "posts/*"
|
||||
let indexCtx =
|
||||
listField "posts" postCtx (return posts) `mappend`
|
||||
defaultContext
|
||||
listField "posts" postCtx (return posts)
|
||||
`mappend` defaultContext
|
||||
getResourceBody
|
||||
>>= applyAsTemplate indexCtx
|
||||
>>= loadAndApplyTemplate "templates/default.html" indexCtx
|
||||
|
@ -111,22 +112,21 @@ main = hakyll $ do
|
|||
|
||||
match "templates/*" $ compile templateBodyCompiler
|
||||
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
feedConfiguration :: FeedConfiguration
|
||||
feedConfiguration =
|
||||
FeedConfiguration
|
||||
{ feedTitle = "Dimitri Lozeve's Blog"
|
||||
, feedDescription = "Recent posts"
|
||||
, feedAuthorName = "Dimitri Lozeve"
|
||||
, feedAuthorEmail = "dimitri+web@lozeve.com"
|
||||
, feedRoot = "https://www.lozeve.com"
|
||||
{ feedTitle = "Dimitri Lozeve's Blog",
|
||||
feedDescription = "Recent posts",
|
||||
feedAuthorName = "Dimitri Lozeve",
|
||||
feedAuthorEmail = "dimitri+web@lozeve.com",
|
||||
feedRoot = "https://www.lozeve.com"
|
||||
}
|
||||
|
||||
postCtx :: Context String
|
||||
postCtx =
|
||||
dateField "date" "%B %e, %Y" `mappend`
|
||||
defaultContext
|
||||
dateField "date" "%B %e, %Y"
|
||||
`mappend` defaultContext
|
||||
|
||||
postCtxWithTags :: Tags -> Context String
|
||||
postCtxWithTags tags = tagsField "tags" tags <> postCtx
|
||||
|
@ -140,33 +140,38 @@ customPandocCompiler withTOC =
|
|||
let customExtensions = extensionsFromList [Ext_latex_macros]
|
||||
defaultExtensions = writerExtensions defaultHakyllWriterOptions
|
||||
newExtensions = defaultExtensions `mappend` customExtensions
|
||||
writerOptions = defaultHakyllWriterOptions
|
||||
{ writerExtensions = newExtensions
|
||||
, writerHTMLMathMethod = MathJax ""
|
||||
writerOptions =
|
||||
defaultHakyllWriterOptions
|
||||
{ writerExtensions = newExtensions,
|
||||
writerHTMLMathMethod = MathJax ""
|
||||
}
|
||||
-- below copied from https://www.gwern.net/hakyll.hs
|
||||
-- below copied from https://github.com/jaspervdj/hakyll/blob/e8ed369edaae1808dffcc22d1c8fb1df7880e065/web/site.hs#L73 because god knows I don't know what this type bullshit is either:
|
||||
-- "When did it get so hard to compile a string to a Pandoc template?"
|
||||
tocTemplate =
|
||||
either error id $ either (error . show) id $
|
||||
runPure $ runWithDefaultPartials $
|
||||
either error id $
|
||||
either (error . show) id $
|
||||
runPure $
|
||||
runWithDefaultPartials $
|
||||
compileTemplate "" "<div id=\"toc\"><h1>Table of Contents</h1>$toc$</div>\n$body$"
|
||||
writerOptionsWithTOC = writerOptions
|
||||
{ writerTableOfContents = True
|
||||
, writerTOCDepth = 2
|
||||
, writerTemplate = Just tocTemplate--"<h1>Table of Contents</h1>$toc$\n$body$"
|
||||
writerOptionsWithTOC =
|
||||
writerOptions
|
||||
{ writerTableOfContents = True,
|
||||
writerTOCDepth = 2,
|
||||
writerTemplate = Just tocTemplate -- "<h1>Table of Contents</h1>$toc$\n$body$"
|
||||
}
|
||||
readerOptions = defaultHakyllReaderOptions
|
||||
in do
|
||||
csl <- load $ fromFilePath "csl/chicago-author-date.csl"
|
||||
bib <- load $ fromFilePath "bib/bibliography.bib"
|
||||
writePandocWith (if withTOC then writerOptionsWithTOC else writerOptions) <$>
|
||||
(getResourceBody >>= readPandocBiblio readerOptions csl bib >>= traverse (return . usingSideNotes))
|
||||
writePandocWith (if withTOC then writerOptionsWithTOC else writerOptions)
|
||||
<$> (getResourceBody >>= readPandocBiblio readerOptions csl bib >>= traverse (return . usingSideNotes))
|
||||
|
||||
type FeedRenderer = FeedConfiguration
|
||||
-> Context String
|
||||
-> [Item String]
|
||||
-> Compiler (Item String)
|
||||
type FeedRenderer =
|
||||
FeedConfiguration ->
|
||||
Context String ->
|
||||
[Item String] ->
|
||||
Compiler (Item String)
|
||||
|
||||
feedCompiler :: FeedRenderer -> Compiler (Item String)
|
||||
feedCompiler renderer =
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue