module Text.Hakyll.Paginate
( PaginateConfiguration (..)
, defaultPaginateConfiguration
, paginate
) where
import Control.Applicative ((<$>))
import Text.Hakyll.Context (Context)
import Text.Hakyll.CreateContext
import Text.Hakyll.HakyllAction
import Text.Hakyll.Util (link)
data PaginateConfiguration = PaginateConfiguration
{
previousLabel :: String
,
nextLabel :: String
,
firstLabel :: String
,
lastLabel :: String
}
defaultPaginateConfiguration :: PaginateConfiguration
defaultPaginateConfiguration = PaginateConfiguration
{ previousLabel = "Previous"
, nextLabel = "Next"
, firstLabel = "First"
, lastLabel = "Last"
}
paginate :: PaginateConfiguration
-> [HakyllAction () Context]
-> [HakyllAction () Context]
paginate configuration renderables = paginate' Nothing renderables (1 :: Int)
where
linkWithLabel f r = Right $ case actionUrl r of
Left l -> createSimpleHakyllAction $
link (f configuration) . ("$root/" ++) <$> l
Right _ -> error "No link found for pagination."
paginate' _ [] _ = []
paginate' maybePrev (x:xs) index =
let (previous, first) = case maybePrev of
(Just r) -> ( linkWithLabel previousLabel r
, linkWithLabel firstLabel (head renderables) )
Nothing -> ( Left $ previousLabel configuration
, Left $ firstLabel configuration )
(next, last') = case xs of
(n:_) -> ( linkWithLabel nextLabel n
, linkWithLabel lastLabel (last renderables) )
[] -> ( Left $ nextLabel configuration
, Left $ lastLabel configuration )
customPage = createCustomPage ""
[ ("previous", previous)
, ("next", next)
, ("first", first)
, ("last", last')
, ("index", Left $ show index)
, ("length", Left $ show $ length renderables)
]
in (x `combine` customPage) : paginate' (Just x) xs (index + 1)