hablo/src/Blog.hs

101 lines
3.3 KiB
Haskell

{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE FlexibleContexts #-}
module Blog (
Blog(..)
, Path(..)
, Skin(..)
, Wording
, build
, get
) 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.Skin (Skin(..))
import qualified Blog.Skin as Skin (build)
import Blog.Wording (Wording)
import qualified Blog.Wording as Wording (build)
import Control.Monad ((>=>), filterM, foldM, forM)
import Control.Monad.Reader (MonadReader, ask)
import Data.Map (Map, insert, lookup)
import qualified Data.Map as Map (empty, fromList)
import Data.Set (Set)
import qualified Data.Set as Set (empty, null, singleton, union)
import Files (File(..), absolute)
import qualified Files (find)
import Page (Page)
import qualified Page (at)
import Prelude hiding (lookup)
import System.Directory (doesFileExist, withCurrentDirectory)
import System.FilePath ((</>), dropTrailingPathSeparator, takeExtension, takeFileName)
import Text.Parsec (ParseError)
type Collection = Map String
type Parsed a = Either ParseError (String, a)
data Blog = Blog {
articles :: Collection Article
, name :: String
, pages :: Collection Page
, path :: Path
, skin :: Skin
, tags :: Map String (Set String)
, wording :: Wording
}
get :: MonadReader Blog m => (Blog -> a) -> m a
get = (<$> ask)
keepOrWarn :: Collection a -> Parsed a -> IO (Collection a)
keepOrWarn accumulator (Left parseErrors) =
forM [show parseErrors, "=> Ignoring this text"] putStrLn
>> return accumulator
keepOrWarn accumulator (Right (key, article)) =
return $ insert key article accumulator
find :: (FilePath -> IO (Parsed a)) -> FilePath -> IO (Collection a)
find parser =
Files.find
>=> filterM isMarkDownFile
>=> mapM parser
>=> foldM keepOrWarn Map.empty
where
isMarkDownFile path = do
let correctExtension = takeExtension path == ".md"
(correctExtension &&) <$> doesFileExist path
tagged :: Collection Article -> FilePath -> IO (String, Set String)
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
maybe Set.empty (\_ -> Set.singleton articleKey) (lookup articleKey collection)
else Set.empty
return (takeFileName path, foldl Set.union Set.empty keys)
discover :: Path -> IO (Collection Article, Collection Page, Collection (Set String))
discover path = do
articles <- find (Article.at) $ articlesPath path
pages <- maybe (return Map.empty) (find (Page.at)) $ pagesPath path
tags <- Map.fromList . filter (not . Set.null . snd)
<$> (Files.find (articlesPath path </> "tags") >>= mapM (articles `tagged`))
return (articles, pages, tags)
build :: Arguments -> IO Blog
build arguments = do
wording <- Wording.build arguments
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, pages, tags) <- discover path
return $ Blog {articles, name, pages, path, skin, tags, wording}