Compare commits

..

No commits in common. "6afa6d55d4fc77527ea37e5716db9a8ddfd66dcf" and "73b42aafa3cd4a2ac76c0c43a5058f9fde63ba4d" have entirely different histories.

6 changed files with 24 additions and 43 deletions

View File

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

58
site.hs
View File

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

2
templates/archive.html Normal file
View File

@ -0,0 +1,2 @@
Here you can find all my previous posts:
$partial("templates/post-list.html")$

View File

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

View File

@ -1,3 +0,0 @@
A list of small and big guides.
$partial("templates/post-list.html")$

View File

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