hablo/src/Collection.hs

54 lines
1.6 KiB
Haskell
Raw Normal View History

2020-03-25 19:47:28 +01:00
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE FlexibleContexts #-}
2020-03-25 19:47:28 +01:00
module Collection (
Collection(..)
, getAll
, title
2020-03-25 19:47:28 +01:00
) where
import Article(Article(metadata))
2020-03-25 19:47:28 +01:00
import Blog (Blog(..), Path(..))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader (MonadReader(..), ReaderT, asks)
import Data.List (sortOn)
import Data.Map ((!))
import qualified Data.Map as Map (elems, filterWithKey, toList)
import Data.Ord (Down(..))
import qualified Data.Set as Set (member)
import Pretty ((.$))
import System.Directory (createDirectoryIfMissing)
import System.FilePath ((</>))
2020-03-25 19:47:28 +01:00
data Collection = Collection {
featured :: [Article]
2020-03-25 19:47:28 +01:00
, basePath :: FilePath
, tag :: Maybe String
}
build :: MonadIO m => [Article] -> Maybe String -> ReaderT Blog m Collection
build featured tag = do
2020-03-25 19:47:28 +01:00
root <- asks $path.$root
let basePath = maybe root (root </>) tag
liftIO $ createDirectoryIfMissing False basePath
return $ Collection {
featured = sortByDate featured, basePath, tag
2020-03-25 19:47:28 +01:00
}
where
sortByDate = sortOn (Down . (! "date") . metadata)
getAll :: ReaderT Blog IO [Collection]
getAll = do
Blog {articles, tags} <- ask
(:)
<$> (build (Map.elems articles) Nothing)
<*> (flip mapM (Map.toList tags) $
\(tag, tagged) -> build (getArticles tagged articles) $ Just tag
)
where
getArticles tagged =
Map.elems . Map.filterWithKey (\k _ -> Set.member k tagged)
title :: MonadReader Blog m => Collection -> m String
title (Collection {tag}) = do
asks $ (\name -> maybe name ((name ++ " - ") ++) tag) . name