1
0
Fork 0
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.
rshyn-site/site.hs

59 lines
1.7 KiB

2 years ago
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid (mappend)
import Hakyll
import Hakyll.Web.Sass (sassCompiler)
--------------------------------------------------------------------------------
2 years ago
config :: Configuration
config =
defaultConfiguration
{ previewPort = 4053
}
2 years ago
main :: IO ()
2 years ago
main = hakyllWith config $ do
-- Static directories
match ("fonts/*" .||. "images/*" .||. "files/*") $ do
route idRoute
compile copyFileCompiler
2 years ago
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 ("posts/*" .||. "publications/*") $ do
2 years ago
route $ setExtension "html"
compile $
pandocCompiler
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
match "index.html" $ do
route idRoute
compile $ do
posts <- loadAll "posts/*"
pubs <- loadAll "publications/*"
let indexCtx = listField "publications" postCtx (return pubs) <> listField "posts" postCtx (return posts) `mappend` defaultContext
2 years ago
getResourceBody
>>= applyAsTemplate indexCtx
>>= loadAndApplyTemplate "templates/default.html" indexCtx
>>= relativizeUrls
match "templates/*" $ compile templateBodyCompiler
--------------------------------------------------------------------------------
postCtx :: Context String
postCtx = modificationTimeField "modded" "%B %e, %Y" `mappend` defaultContext