hablo/src/Collection.hs

48 lines
1.4 KiB
Haskell

{-# LANGUAGE NamedFieldPuns #-}
module Collection (
Collection(..)
, getAll
) where
import Article(Article(..))
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.Posix ((</>))
data Collection = Collection {
articlesFeatured :: [Article]
, basePath :: FilePath
, tag :: Maybe String
}
build :: MonadIO m => [Article] -> Maybe String -> ReaderT Blog m Collection
build articlesFeatured tag = do
root <- asks $path.$root
let basePath = maybe root (root </>) tag
liftIO $ createDirectoryIfMissing False basePath
return $ Collection {
articlesFeatured = sortByDate articlesFeatured, basePath, tag
}
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)