hablo/src/Blog.hs

82 lines
2.7 KiB
Haskell

{-# LANGUAGE NamedFieldPuns #-}
module Blog (
Blog(..)
, get
) where
import Arguments (Arguments(bannerPath, blogName, headPath, sourceDir))
import qualified Arguments (previewArticlesCount, previewLinesCount)
import Article (Article)
import qualified Article (at)
import Control.Monad ((>=>), filterM, forM)
import Data.Map (Map)
import qualified Data.Map as Map (fromList, member)
import Data.Set (Set)
import qualified Data.Set as Set (empty, null, singleton, union)
import System.Directory (doesFileExist, listDirectory, withCurrentDirectory)
import System.FilePath ((</>), dropTrailingPathSeparator, splitFileName, takeExtension, takeFileName)
import System.Posix.Types (FileID)
import System.Posix.Files (getFileStatus, fileID)
type Collection = Map FileID Article
data Blog = Blog {
articles :: Collection
, name :: String
, previewArticlesCount :: Int
, previewLinesCount :: Int
, root :: FilePath
, tags :: Map String (Set FileID)
, customBanner :: Maybe String
, customHead :: Maybe String
}
find :: FilePath -> IO [FilePath]
find path =
fmap (path </>) <$> listDirectory path
findArticles :: Int -> FilePath -> IO (Map FileID Article)
findArticles linesCount =
find
>=> filterM isMarkDownFile
>=> mapM (Article.at linesCount)
>=> return . Map.fromList
where
isMarkDownFile path = do
let correctExtension = takeExtension path == ".md"
(correctExtension &&) <$> doesFileExist path
tagged :: Collection -> FilePath -> IO (String, Set FileID)
tagged collection path = do
links <- find path
fileIDs <- forM links $ \link -> do
fileExists <- doesFileExist link
if fileExists
then do
inode <- fileID <$> getFileStatus link
return $ if Map.member inode collection then Set.singleton inode else Set.empty
else return Set.empty
return (takeFileName path, foldl Set.union Set.empty fileIDs)
get :: Arguments -> IO Blog
get arguments = withCurrentDirectory root $ do
let name = maybe (takeFileName $ dropTrailingPathSeparator root) id $ blogName arguments
let previewLinesCount = Arguments.previewLinesCount arguments
articles <- findArticles previewLinesCount articlesPath
tags <- Map.fromList . filter (not . Set.null . snd)
<$> (find (articlesPath </> "tags") >>= mapM (articles `tagged`))
customBanner <- mapM readFile $ bannerPath arguments
customHead <- mapM readFile $ headPath arguments
return $ Blog {
articles
, name
, previewArticlesCount = Arguments.previewArticlesCount arguments
, previewLinesCount
, root
, tags
, customBanner
, customHead
}
where
(root, articlesPath) = splitFileName $ sourceDir arguments