aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorPaweł Dybiec <pawel@dybiec.info>2023-11-21 00:35:37 +0000
committerPaweł Dybiec <pawel@dybiec.info>2023-11-21 00:35:37 +0000
commit93b3894d5160809deba500252a4797018314f0df (patch)
treee043aabac0deb1babb730c9bc4eaeed4da705850
parentUpdate about + minor details (diff)
Hide non-published posts from the listmain
-rw-r--r--dybiec-info.cabal2
-rw-r--r--site.hs103
-rw-r--r--templates/post.html2
3 files changed, 58 insertions, 49 deletions
diff --git a/dybiec-info.cabal b/dybiec-info.cabal
index 7c2eac3..dbdd72d 100644
--- a/dybiec-info.cabal
+++ b/dybiec-info.cabal
@@ -11,5 +11,5 @@ homepage: https://git.dybiec.info/website
executable site
main-is: site.hs
build-depends: base == 4.*
- , hakyll == 4.16.*
+ , hakyll >= 4.15
ghc-options: -threaded
diff --git a/site.hs b/site.hs
index d32fd49..47230de 100644
--- a/site.hs
+++ b/site.hs
@@ -1,67 +1,74 @@
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
-import Data.Monoid (mappend)
-import Hakyll
+import Control.Monad (filterM)
+import Data.Maybe (isJust)
+import Data.Monoid (mappend)
+import Hakyll
--------------------------------------------------------------------------------
main :: IO ()
main = hakyll $ do
+ match "images/*" $ do
+ route idRoute
+ compile copyFileCompiler
- match "images/*" $ do
- route idRoute
- compile copyFileCompiler
+ match "static/*" $ do
+ route idRoute
+ compile copyFileCompiler
- match "static/*" $ do
- route idRoute
- compile copyFileCompiler
+ match (fromList ["robots.txt"]) $ do
+ route idRoute
+ compile copyFileCompiler
- match (fromList ["robots.txt"]) $ do
- route idRoute
- compile copyFileCompiler
+ match "css/*" $ compile compressCssCompiler
+ create ["style.css"] $ do
+ route idRoute
+ compile $ do
+ csses <- loadAll "css/*.css"
+ makeItem $ unlines $ map itemBody csses
- match "css/*" $ compile compressCssCompiler
- create ["style.css"] $ do
- route idRoute
- compile $ do
- csses <- loadAll "css/*.css"
- makeItem $ unlines $ map itemBody csses
-
- match (fromList ["index.md"]) $ do
- route $ setExtension "html"
- compile $ pandocCompiler
- >>= loadAndApplyTemplate "templates/default.html" defaultContext
- >>= relativizeUrls
-
+ match (fromList ["index.md"]) $ do
+ route $ setExtension "html"
+ compile $
+ pandocCompiler
+ >>= 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/*" $ do
+ route $ setExtension "html"
+ compile $
+ pandocCompiler
+ >>= loadAndApplyTemplate "templates/post.html" postCtx
+ >>= loadAndApplyTemplate "templates/default.html" postCtx
+ >>= relativizeUrls
- create ["posts.html"] $ do
- route idRoute
- compile $ do
- posts <- recentFirst =<< loadAll "posts/*"
- let archiveCtx =
- listField "posts" postCtx (return posts) `mappend`
- constField "title" "Archives" `mappend`
- defaultContext
+ create ["posts.html"] $ do
+ route idRoute
+ compile $ do
+ posts <- recentFirst =<< filterPublished =<< 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 "templates/*" $ compile templateBodyCompiler
+ makeItem ""
+ >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
+ >>= loadAndApplyTemplate "templates/default.html" archiveCtx
+ >>= relativizeUrls
+ match "templates/*" $ compile templateBodyCompiler
--------------------------------------------------------------------------------
postCtx :: Context String
postCtx =
- dateField "date" "%B %e, %Y" `mappend`
- defaultContext
+ dateField "date" "%B %e, %Y"
+ `mappend` defaultContext
+
+filterPublished :: (MonadMetadata m, MonadFail m) => [Item a] -> m [Item a]
+filterPublished = filterM $ isPublished . itemIdentifier
+ where
+ isPublished :: (MonadMetadata m, MonadFail m) => Identifier -> m Bool
+ isPublished id' = do
+ metadata <- getMetadata id'
+ pure $ isJust $ lookupString "date" metadata
diff --git a/templates/post.html b/templates/post.html
index 732149b..30b75a1 100644
--- a/templates/post.html
+++ b/templates/post.html
@@ -1,6 +1,8 @@
<article>
<section class="header">
+ $if(date)$
Posted on $date$
+ $endif$
$if(author)$
by $author$
$endif$