hablo/src/ArticlesList.hs

53 lines
1.8 KiB
Haskell

{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
module ArticlesList (
ArticlesList(..)
, description
, getArticles
, otherURL
, rssLinkTexts
) where
import Article (Article)
import Blog (Blog(..), Skin(..))
import Blog.Wording (render)
import Collection (Collection(..))
import Control.Monad.Reader (MonadReader, asks)
import Data.Text (Text, pack)
import Files (absoluteLink)
import Pretty ((.$))
import System.FilePath.Posix ((</>))
data ArticlesList = ArticlesList {
full :: Bool
, collection :: Collection
}
getArticles :: MonadReader Blog m => ArticlesList -> m [Article]
getArticles (ArticlesList {full, collection = Collection {featured}}) = do
limit <- take <$> (asks $skin.$previewArticlesCount)
return $ if full then featured else limit featured
otherURL :: ArticlesList -> String
otherURL (ArticlesList {full, collection}) = absoluteLink $
(if full then id else (</> "all.html")) . maybe "" id $ tag collection
description :: MonadReader Blog m => ArticlesList -> m Text
description (ArticlesList {full, collection}) =
getDescription (full, tag collection) <$> asks wording
where
getDescription (True, Nothing) = render "allPage" []
getDescription (True, Just tag) = render "allTaggedPage" [("tag", pack tag)]
getDescription (False, Nothing) = render "latestPage" []
getDescription (False, Just tag) =
render "latestTaggedPage" [("tag", pack tag)]
rssLinkTexts :: MonadReader Blog m => ArticlesList -> m (Text, Text)
rssLinkTexts (ArticlesList {collection}) = do
text <- asks $wording.$(render "rssLink" [])
title <- asks $wording.$(render "rssTitle" environment)
return (text, title)
where
environment = maybe [] (\v -> [("tag", pack v)]) $ tag collection