Support for guides

This commit is contained in:
Mats Rauhala 2018-09-20 21:57:49 +03:00
parent 73b42aafa3
commit d89a2bae5c
Signed by: MasseR
GPG Key ID: 1C18445948FFF87B
4 changed files with 40 additions and 22 deletions

View File

@ -7,5 +7,6 @@ executable site
main-is: site.hs
build-depends: base == 4.*
, hakyll == 4.10.*
, time
ghc-options: -threaded
default-language: Haskell2010

58
site.hs
View File

@ -2,6 +2,8 @@
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid (mappend)
import Hakyll
import Data.List (sortBy, sortOn)
import Data.Time (formatTime, defaultTimeLocale)
--------------------------------------------------------------------------------
@ -25,34 +27,38 @@ main = hakyll $ do
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
-- match "posts/*" $ do
-- route $ setExtension "html"
-- compile $ pandocCompiler
-- >>= loadAndApplyTemplate "templates/post.html" postCtx
-- >>= loadAndApplyTemplate "templates/default.html" postCtx
-- >>= relativizeUrls
match "posts/guides/*" $ do
route $ setExtension "html"
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
-- create ["archive.html"] $ do
-- route idRoute
-- compile $ do
-- posts <- recentFirst =<< loadAll "posts/*"
-- let archiveCtx =
-- listField "posts" postCtx (return posts) `mappend`
-- constField "title" "Archives" `mappend`
-- defaultContext
--
-- makeItem ""
-- >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
-- >>= loadAndApplyTemplate "templates/default.html" archiveCtx
-- >>= relativizeUrls
match "posts/brainstorming/*" $ do
route $ setExtension "html"
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
create ["guides.html"] $ do
route idRoute
compile $ do
posts <- modFirst =<< loadAll "posts/guides/*"
let archiveCtx =
listField "posts" postCtx (return posts) `mappend`
constField "title" "Archives" `mappend`
defaultContext
makeItem ""
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
>>= relativizeUrls
match "index.html" $ do
route idRoute
compile $ do
posts <- recentFirst =<< loadAll "posts/*"
let indexCtx =
listField "posts" postCtx (return posts) `mappend`
constField "title" "Home" `mappend`
defaultContext
@ -63,9 +69,19 @@ main = hakyll $ do
match "templates/*" $ compile templateBodyCompiler
modFirst :: [Item a] -> Compiler [Item a]
modFirst = fmap reverse . modified
where
modified = sortByM (getItemModificationTime . itemIdentifier)
sortByM f xs = map fst . sortOn snd <$> mapM (\x -> (,) x <$> f x) xs
--------------------------------------------------------------------------------
postCtx :: Context String
postCtx =
dateField "date" "%B %e, %Y" `mappend`
modifiedField "modified" "%B %e, %Y" `mappend`
defaultContext
where
modifiedField key format = field key $ \i -> do
time <- getItemModificationTime $ itemIdentifier i
return $ formatTime defaultTimeLocale format time

View File

@ -14,6 +14,7 @@
</div>
<nav>
<a href="/">Home</a>
<a href="/guides.html">Guides</a>
<a href="/about.html">About</a>
<a href="/contact.html">Contact</a>
</nav>

View File

@ -1,6 +1,6 @@
<article>
<section class="header">
Posted on $date$
Posted on $date$, modified on $modified$
$if(author)$
by $author$
$endif$