chronological, recentFirst now respects metadata

Solves #111
This commit is contained in:
Simonas Kazlauskas 2013-02-23 12:47:01 +02:00
parent 8c575ae521
commit 718388495b

View file

@ -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