summaryrefslogtreecommitdiff
path: root/web/site.hs
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2019-01-27 16:40:40 +0100
committerJasper Van der Jeugt <m@jaspervdj.be>2019-01-27 16:40:40 +0100
commitd832cd80ddf43872532db8943f310eed4edb7fe5 (patch)
treea088d3b39f98267197f7cae71eb56f47ecb39f3e /web/site.hs
parenta983c8cbc917ffa3ce81d2540b50bdb321588b92 (diff)
downloadhakyll-d832cd80ddf43872532db8943f310eed4edb7fe5.tar.gz
Refactor tutorials on hakyll website
Diffstat (limited to 'web/site.hs')
-rw-r--r--web/site.hs45
1 files changed, 13 insertions, 32 deletions
diff --git a/web/site.hs b/web/site.hs
index a20d15b..2bfaf3e 100644
--- a/web/site.hs
+++ b/web/site.hs
@@ -1,8 +1,7 @@
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Control.Arrow (second)
-import Control.Monad (forM_)
-import Data.Char (isDigit)
+import Control.Monad (filterM, forM_)
import Data.List (isPrefixOf, sortBy)
import Data.Monoid ((<>))
import Data.Ord (comparing)
@@ -57,17 +56,11 @@ main = hakyllWith config $ do
create ["tutorials.html"] $ do
route idRoute
compile $ do
- tuts <-
+ ctx <- tutorialsCtx <$>
sortBy (comparing itemIdentifier) <$> loadAll "tutorials/*"
-
- let tutorialsCtx =
- constField "title" "Tutorials" `mappend`
- listField "tutorials" tutorialCtx (return tuts) `mappend`
- defaultContext
-
makeItem ""
- >>= loadAndApplyTemplate "templates/tutorials.html" tutorialsCtx
- >>= loadAndApplyTemplate "templates/default.html" tutorialsCtx
+ >>= loadAndApplyTemplate "templates/tutorials.html" ctx
+ >>= loadAndApplyTemplate "templates/default.html" ctx
>>= relativizeUrls
-- Templates
@@ -109,27 +102,15 @@ hackage url
--------------------------------------------------------------------------------
-data TutorialType = SeriesTutorial | ArticlesTutorial | ExternalTutorial
- deriving (Eq)
-
-
---------------------------------------------------------------------------------
-- | Partition tutorials into tutorial series, other articles, external articles
-tutorialCtx :: Context String
-tutorialCtx =
- field "isSeries" (isTutorialType SeriesTutorial) <>
- field "isArticle" (isTutorialType ArticlesTutorial) <>
- field "isExternal" (isTutorialType ExternalTutorial) <>
+tutorialsCtx :: [Item String] -> Context String
+tutorialsCtx tuts =
+ constField "title" "Tutorials" <>
+ listField "main" defaultContext (ofType "main") <>
+ listField "articles" defaultContext (ofType "article") <>
+ listField "externals" defaultContext (ofType "external") <>
defaultContext
where
- getTutorialType item = do
- mbExternal <- getMetadataField (itemIdentifier item) "external"
- return $ case mbExternal of
- Just _ -> ExternalTutorial
- _ -> case splitPath (toFilePath $ itemIdentifier item) of
- [_, (x : _)] -> if isDigit x then SeriesTutorial else ArticlesTutorial
- _ -> ArticlesTutorial
-
- isTutorialType ty0 item = do
- ty1 <- getTutorialType item
- if ty0 == ty1 then return "yes" else fail "no"
+ ofType ty = filterM (\item -> do
+ mbType <- getMetadataField (itemIdentifier item) "type"
+ return $ Just ty == mbType) tuts