summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorSimonas Kazlauskas <git@kazlauskas.me>2013-02-23 12:47:01 +0200
committerSimonas Kazlauskas <git@kazlauskas.me>2013-02-23 12:47:01 +0200
commit718388495b41089eddcac9ae55aae4ca68620505 (patch)
tree4403ed1226fa7832c5471ee66c2f22e29beaa756 /src
parent8c575ae52115f09d5b6e53ed409d934f5168de59 (diff)
downloadhakyll-718388495b41089eddcac9ae55aae4ca68620505.tar.gz
chronological, recentFirst now respects metadata
Solves #111
Diffstat (limited to 'src')
-rw-r--r--src/Hakyll/Web/Template/List.hs15
1 files changed, 10 insertions, 5 deletions
diff --git a/src/Hakyll/Web/Template/List.hs b/src/Hakyll/Web/Template/List.hs
index 6d2a341..5f94369 100644
--- a/src/Hakyll/Web/Template/List.hs
+++ b/src/Hakyll/Web/Template/List.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE TupleSections #-}
--------------------------------------------------------------------------------
-- | Provides an easy way to combine several items in a list. The applications
-- are obvious:
@@ -16,9 +17,11 @@ module Hakyll.Web.Template.List
--------------------------------------------------------------------------------
+import Control.Monad (liftM)
import Data.List (intersperse, sortBy)
import Data.Ord (comparing)
import System.FilePath (takeBaseName)
+import System.Locale (defaultTimeLocale)
--------------------------------------------------------------------------------
@@ -56,11 +59,13 @@ applyJoinTemplateList delimiter tpl context items = do
-- | 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 :: [Item a] -> [Item a]
-chronological = sortBy $ comparing $ takeBaseName . toFilePath . itemIdentifier
-
+chronological :: [Item a] -> Compiler [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 :: [Item a] -> [Item a]
-recentFirst = reverse . chronological
+recentFirst :: [Item a] -> Compiler [Item a]
+recentFirst i = return . reverse =<< chronological i