Rename ArticlesLists' description and title for more clarity and reuse in RSS feeds

This commit is contained in:
Tissevert 2020-03-23 16:18:22 +01:00
parent dfd3a78b79
commit 2fba3d8b6a
3 changed files with 22 additions and 15 deletions

View File

@ -3,14 +3,15 @@
{-# LANGUAGE FlexibleContexts #-}
module ArticlesList (
ArticlesList(..)
, description
, otherUrl
, pageTitle
, title
) where
import Article (Article)
import Blog (Blog(..), get)
import Blog (Blog(..))
import Blog.Wording (render)
import Control.Monad.Reader (MonadReader)
import Control.Monad.Reader (MonadReader, asks)
import Data.Text (Text, pack)
import Files (absoluteLink)
import System.FilePath.Posix ((</>))
@ -25,13 +26,19 @@ otherUrl :: ArticlesList -> String
otherUrl (ArticlesList {full, tagged}) = absoluteLink $
(if full then id else (</> "all.html")) $ maybe "" id tagged
pageTitle :: (MonadReader Blog m) => ArticlesList -> m Text
pageTitle (ArticlesList {full, tagged}) = title (full, tagged) <$> Blog.get wording
title :: MonadReader Blog m => ArticlesList -> m String
title (ArticlesList {tagged}) = do
asks $ (\name -> maybe name ((name ++ " - ") ++) tagged) . name
description :: MonadReader Blog m => ArticlesList -> m Text
description (ArticlesList {full, tagged}) =
getDescription (full, tagged) <$> asks wording
where
title (True, Nothing) = render "allPage" []
title (True, Just tag) = render "allTaggedPage" [("tag", pack tag)]
title (False, Nothing) = render "latestPage" []
title (False, Just tag) = render "latestTaggedPage" [("tag", pack tag)]
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)]

View File

@ -6,7 +6,7 @@ module DOM (
import Article (Article(..))
import qualified Article (preview)
import ArticlesList (ArticlesList(..), otherUrl, pageTitle)
import ArticlesList (ArticlesList(..), otherUrl, description)
import Blog (Blog(..), Path(..), Skin(..), URL(..))
import qualified Blog (get)
import Blog.Wording (render)
@ -32,7 +32,7 @@ instance Page Article where
instance Page ArticlesList where
content al@(ArticlesList {featured, full}) = do
preview <- Article.preview <$> (Blog.get $skin.$previewLinesCount)
h2_ . toHtml =<< pageTitle al
h2_ . toHtml =<< description al
a_ [href_ . pack $ otherUrl al] . toHtml =<< otherLink
div_ [class_ "articles"] (
mapM_ (article False . preview) featured

View File

@ -8,7 +8,8 @@ module DOM.Card (
) where
import qualified Article (Article(..))
import ArticlesList (ArticlesList(..), pageTitle)
import ArticlesList (ArticlesList(..))
import qualified ArticlesList (description, title)
import Blog (Blog(..), Skin(..))
import qualified Blog (get)
import Control.Applicative ((<|>))
@ -64,8 +65,8 @@ instance HasCard Article.Article where
instance HasCard ArticlesList where
getCard al = do
cardTitle <- getTitle <$> Blog.get name
description <- pageTitle al
cardTitle <- ArticlesList.title al
description <- ArticlesList.description al
return $ Card {
cardType = "website"
, description
@ -74,5 +75,4 @@ instance HasCard ArticlesList where
, urlPath = maybe "" ('/':) (tagged al) ++ file
}
where
getTitle name = maybe name ((name ++ " - ") ++) $ tagged al
file = '/' : (if full al then "all" else "index") ++ ".html"