blob: 8eadd53eb95365a11fa405b51a1190adb83cc53b (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
|
--------------------------------------------------------------------------------
-- | Provides an easy way to combine several items in a list. The applications
-- are obvious:
--
-- * A post list on a blog
--
-- * An image list in a gallery
--
-- * A sitemap
{-# LANGUAGE TupleSections #-}
module Hakyll.Web.Template.List
( applyTemplateList
, applyJoinTemplateList
, chronological
, recentFirst
) where
--------------------------------------------------------------------------------
import Control.Monad (liftM)
import Data.List (intersperse, sortBy)
import Data.Ord (comparing)
import System.Locale (defaultTimeLocale)
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
import Hakyll.Core.Item
import Hakyll.Core.Metadata
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
--------------------------------------------------------------------------------
-- | Generate a string of a listing of pages, after applying a template to each
-- page.
applyTemplateList :: Template
-> Context a
-> [Item a]
-> Compiler String
applyTemplateList = applyJoinTemplateList ""
--------------------------------------------------------------------------------
-- | Join a listing of pages with a string in between, after applying a template
-- to each page.
applyJoinTemplateList :: String
-> Template
-> Context a
-> [Item a]
-> Compiler String
applyJoinTemplateList delimiter tpl context items = do
items' <- mapM (applyTemplate tpl context) items
return $ concat $ intersperse delimiter $ map itemBody items'
--------------------------------------------------------------------------------
-- | Sort pages chronologically. This function assumes that the pages have a
-- @year-month-day-title.extension@ naming scheme -- as is the convention in
-- Hakyll.
chronological :: MonadMetadata m => [Item a] -> m [Item a]
chronological =
sortByM $ getItemUTC defaultTimeLocale . itemIdentifier
where
sortByM :: (Monad m, Ord k) => (a -> m k) -> [a] -> m [a]
sortByM f xs = liftM (map fst . sortBy (comparing snd)) $
mapM (\x -> liftM (x,) (f x)) xs
--------------------------------------------------------------------------------
-- | The reverse of 'chronological'
recentFirst :: (MonadMetadata m, Functor m) => [Item a] -> m [Item a]
recentFirst = fmap reverse . chronological
|