Skip to content

Commit

Permalink
Update example & tutorials with new recentFirst
Browse files Browse the repository at this point in the history
  • Loading branch information
jaspervdj committed Feb 24, 2013
1 parent 9b60358 commit b91c8be
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 11 deletions.
10 changes: 5 additions & 5 deletions data/example/site.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative ((<$>))
import Data.Monoid (mappend)
import Data.Monoid (mappend)
import Hakyll


Expand Down Expand Up @@ -46,7 +45,8 @@ main = hakyll $ do
match "index.html" $ do
route idRoute
compile $ do
let indexCtx = field "posts" $ \_ -> postList (take 3 . recentFirst)
let indexCtx = field "posts" $ \_ ->
postList $ fmap (take 3) . recentFirst

getResourceBody
>>= applyAsTemplate indexCtx
Expand All @@ -64,9 +64,9 @@ postCtx =


--------------------------------------------------------------------------------
postList :: ([Item String] -> [Item String]) -> Compiler String
postList :: ([Item String] -> Compiler [Item String]) -> Compiler String
postList sortFilter = do
posts <- sortFilter <$> loadAll "posts/*"
posts <- sortFilter =<< loadAll "posts/*"
itemTpl <- loadBody "templates/post-item.html"
list <- applyTemplateList itemTpl postCtx posts
return list
5 changes: 3 additions & 2 deletions web/site.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,9 @@ import Control.Applicative ((<$>))
import Control.Arrow (second)
import Control.Monad (forM_)
import Data.Char (isDigit)
import Data.List (isPrefixOf, partition)
import Data.List (isPrefixOf, partition, sortBy)
import Data.Monoid (mappend)
import Data.Ord (comparing)
import Hakyll
import System.FilePath (dropTrailingPathSeparator, splitPath)
import Text.Pandoc
Expand Down Expand Up @@ -55,7 +56,7 @@ main = hakyllWith config $ do
tutorials <- loadAll "tutorials/*"
itemTpl <- loadBody "templates/tutorial-item.html"
let (series, articles) = partitionTutorials $
chronological tutorials
sortBy (comparing itemIdentifier) tutorials

series' <- applyTemplateList itemTpl defaultContext series
articles' <- applyTemplateList itemTpl defaultContext articles
Expand Down
8 changes: 4 additions & 4 deletions web/tutorials/04-compilers.markdown
Original file line number Diff line number Diff line change
Expand Up @@ -158,18 +158,18 @@ We can reproduce a list of items in the archive using the following code:

```haskell
compile $ do
posts <- recentFirst <$> loadAll "posts/*"
posts <- recentFirst =<< loadAll "posts/*"
itemTpl <- loadBody "templates/post-item.html"
list <- applyTemplateList itemTpl postCtx posts
makeItem list
```

`recentFirst` sorts items by date. This relies on the convention that posts are
always named `YYYY-MM-DD-title.extension` in Hakyll -- if you use some other
format, you'll have to write some other sorting method.
always named `YYYY-MM-DD-title.extension` in Hakyll -- or that the date must be
present in the metadata.

```haskell
recentFirst :: [Item a] -> [Item a]
recentFirst :: [Item a] -> Compiler [Item a]
```

After loading and sorting the items, we load a template for the posts.
Expand Down

0 comments on commit b91c8be

Please sign in to comment.