You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
76 lines
2.4 KiB
76 lines
2.4 KiB
--------------------------------------------------------------------------------
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
import Data.Monoid (mappend)
|
|
import Hakyll
|
|
import Hakyll.Web.Sass (sassCompiler)
|
|
|
|
--------------------------------------------------------------------------------
|
|
config :: Configuration
|
|
config =
|
|
defaultConfiguration
|
|
{ previewPort = 4053
|
|
}
|
|
|
|
main :: IO ()
|
|
main = hakyllWith config $ do
|
|
-- Static directories
|
|
|
|
match ("fonts/*" .||. "images/*" .||. "files/*" .||. "film/*" .||. "font-awesome/**" .||. "favicon/*") $ do
|
|
route idRoute
|
|
compile copyFileCompiler
|
|
|
|
scssDependency <- makePatternDependency "css/**.scss"
|
|
rulesExtraDependencies [scssDependency] $
|
|
match "css/default.scss" $
|
|
do
|
|
route $ setExtension "css"
|
|
compile (fmap compressCss <$> sassCompiler)
|
|
|
|
match "css/*" $ do
|
|
route idRoute
|
|
compile compressCssCompiler
|
|
|
|
match "index.html" $ do
|
|
route idRoute
|
|
compile $ do
|
|
posts <- recentFirst =<< loadAll "posts/*"
|
|
pubs <- recentFirst =<< loadAll "publications/*"
|
|
|
|
let indexCtx = listField "publications" postCtx (return pubs) <> listField "posts" postCtx (return posts) `mappend` defaultContext
|
|
|
|
getResourceBody
|
|
>>= applyAsTemplate indexCtx
|
|
>>= loadAndApplyTemplate "templates/default.html" indexCtx
|
|
>>= relativizeUrls
|
|
|
|
match ("posts/*" .||. "publications/*") $ do
|
|
route $ setExtension "html"
|
|
compile $
|
|
pandocCompiler
|
|
>>= loadAndApplyTemplate "templates/post.html" postCtx
|
|
>>= loadAndApplyTemplate "templates/default.html" postCtx
|
|
>>= relativizeUrls
|
|
|
|
match "gallery.html" $ do
|
|
route idRoute
|
|
compile $ do
|
|
film <- loadAll "film/*"
|
|
filmH <- loadBody "templates/photo.html"
|
|
|
|
let imgCtx :: Context CopyFile
|
|
imgCtx = urlField "url" <> missingField
|
|
|
|
art <- applyTemplateList filmH imgCtx film
|
|
let galleryCtx = constField "art" art <> defaultContext
|
|
|
|
getResourceBody
|
|
>>= loadAndApplyTemplate "templates/gallery.html" galleryCtx
|
|
>>= loadAndApplyTemplate "templates/default.html" galleryCtx
|
|
>>= relativizeUrls
|
|
|
|
match "templates/*" $ compile templateBodyCompiler
|
|
|
|
--------------------------------------------------------------------------------
|
|
postCtx :: Context String
|
|
postCtx = mconcat [modificationTimeField "modded" "%B %e, %Y", dateField "parsed-date" "%B %e, %Y", defaultContext]
|
|
|