summaryrefslogtreecommitdiff
path: root/src/Hakyll/Web
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll/Web')
-rw-r--r--src/Hakyll/Web/Template/Context.hs7
-rw-r--r--src/Hakyll/Web/Template/List.hs18
2 files changed, 17 insertions, 8 deletions
diff --git a/src/Hakyll/Web/Template/Context.hs b/src/Hakyll/Web/Template/Context.hs
index 8aab989..1a9aba3 100644
--- a/src/Hakyll/Web/Template/Context.hs
+++ b/src/Hakyll/Web/Template/Context.hs
@@ -167,9 +167,10 @@ dateFieldWith locale key format = field key $ \i -> do
-- | Parser to try to extract and parse the time from the @published@
-- field or from the filename. See 'renderDateField' for more information.
-- Exported for user convenience.
-getItemUTC :: TimeLocale -- ^ Output time locale
+getItemUTC :: MonadMetadata m
+ => TimeLocale -- ^ Output time locale
-> Identifier -- ^ Input page
- -> Compiler UTCTime -- ^ Parsed UTCTime
+ -> m UTCTime -- ^ Parsed UTCTime
getItemUTC locale id' = do
metadata <- getMetadata id'
let tryField k fmt = M.lookup k metadata >>= parseTime' fmt
@@ -180,7 +181,7 @@ getItemUTC locale id' = do
[tryField "date" fmt | fmt <- formats] ++
[parseTime' "%Y-%m-%d" $ intercalate "-" $ take 3 $ splitAll "-" fn]
where
- empty' = compilerThrow $ "Hakyll.Web.Template.Context.getItemUTC: " ++
+ empty' = fail $ "Hakyll.Web.Template.Context.getItemUTC: " ++
"could not parse time for " ++ show id'
parseTime' = parseTime locale
formats =
diff --git a/src/Hakyll/Web/Template/List.hs b/src/Hakyll/Web/Template/List.hs
index 6d2a341..9571b9e 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,15 +17,18 @@ 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)
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
import Hakyll.Core.Identifier
import Hakyll.Core.Item
+import Hakyll.Core.Metadata
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
@@ -56,11 +60,15 @@ 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 :: 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 :: [Item a] -> [Item a]
-recentFirst = reverse . chronological
+recentFirst :: (MonadMetadata m, Functor m) => [Item a] -> m [Item a]
+recentFirst = fmap reverse . chronological