hablo/src/Blog.hs

115 lines
3.7 KiB
Haskell
Raw Normal View History

2019-01-27 21:41:21 +01:00
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
2019-01-27 21:41:21 +01:00
module Blog (
Blog(..)
, Path(..)
, Renderer
, Skin(..)
, URL(..)
, Wording
, build
, template
2019-01-27 21:41:21 +01:00
) where
import Arguments (Arguments)
import qualified Arguments (name, sourceDir)
import Article (Article)
import qualified Article (at, getKey)
import Blog.Path (Path(..))
import qualified Blog.Path as Path (build)
import Blog.Template (Environment, Templates, render)
import qualified Blog.Template as Template (build)
import Blog.Skin (Skin(..))
import qualified Blog.Skin as Skin (build)
import Blog.URL (URL(..))
import qualified Blog.URL as URL (build)
import Blog.Wording (Wording)
2019-02-17 19:52:28 +01:00
import qualified Blog.Wording as Wording (build)
import Control.Monad ((>=>), filterM, foldM, forM)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Reader (MonadReader, asks)
import Data.Map (Map, insert, lookup)
import qualified Data.Map as Map (empty, fromList)
2019-01-27 21:41:21 +01:00
import Data.Set (Set)
import qualified Data.Set as Set (empty, null, singleton, union)
import Data.Text (Text)
import Files (File(..), absolute)
import qualified Files (find)
2019-02-18 15:16:34 +01:00
import Prelude hiding (lookup)
import System.Directory (doesFileExist, withCurrentDirectory)
import System.FilePath ((</>), dropTrailingPathSeparator, takeExtension, takeFileName)
import Text.Parsec (ParseError)
2019-01-27 21:41:21 +01:00
type Collection = Map String Article
2019-01-27 21:41:21 +01:00
data Blog = Blog {
articles :: Collection
, hasRSS :: Bool
2019-01-27 21:41:21 +01:00
, name :: String
, path :: Path
, skin :: Skin
, tags :: Map String (Set String)
, templates :: Templates
, urls :: URL
2019-02-17 19:52:28 +01:00
, wording :: Wording
2019-01-27 21:41:21 +01:00
}
type Renderer m = (MonadIO m, MonadReader Blog m)
template :: Renderer m => String -> Environment -> m Text
template key environment = asks templates >>= render key environment
keepOrWarn :: Map String Article -> Either ParseError (String, Article) -> IO (Map String Article)
keepOrWarn accumulator (Left parseErrors) =
forM [show parseErrors, "=> Ignoring this article"] putStrLn
>> return accumulator
keepOrWarn accumulator (Right (key, article)) =
return $ insert key article accumulator
findArticles :: FilePath -> IO (Map String Article)
2019-02-15 14:13:43 +01:00
findArticles =
Files.find
>=> filterM isMarkDownFile
2019-02-15 14:13:43 +01:00
>=> mapM Article.at
>=> foldM keepOrWarn Map.empty
2019-01-27 21:41:21 +01:00
where
isMarkDownFile path = do
let correctExtension = takeExtension path == ".md"
(correctExtension &&) <$> doesFileExist path
2019-01-27 21:41:21 +01:00
tagged :: Collection -> FilePath -> IO (String, Set String)
2019-01-27 21:41:21 +01:00
tagged collection path = do
links <- Files.find path
keys <- forM links $ \link -> do
fileExists <- doesFileExist link
return $ if fileExists
then let articleKey = Article.getKey link in
2019-02-18 15:16:34 +01:00
maybe Set.empty (\_ -> Set.singleton articleKey) (lookup articleKey collection)
else Set.empty
return (takeFileName path, foldl Set.union Set.empty keys)
2019-01-27 21:41:21 +01:00
discover :: Path -> IO (Collection, Map String (Set String))
discover path = do
articles <- findArticles $ articlesPath path
2019-01-27 21:41:21 +01:00
tags <- Map.fromList . filter (not . Set.null . snd)
<$> (Files.find (articlesPath path </> "tags") >>= mapM (articles `tagged`))
return (articles, tags)
build :: Arguments -> IO Blog
build arguments = do
urls <- URL.build arguments
let hasRSS = maybe False (\_-> True) $ rss urls
wording <- Wording.build arguments
templates <- Template.build wording
root <- Files.absolute . Dir $ Arguments.sourceDir arguments
withCurrentDirectory root $ do
path <- Path.build root arguments
let name = maybe (takeFileName $ dropTrailingPathSeparator root) id
$ Arguments.name arguments
skin <- Skin.build name arguments
(articles, tags) <- discover path
return $ Blog {
articles, hasRSS, name, path, skin, tags, templates, urls, wording
}