{-# 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, forM) import Control.Monad.Reader (MonadReader, ask) import Data.Either (rights) import Data.Map (Map, lookup) import qualified Data.Map as Map (fromList) import Data.Set (Set) import qualified Data.Set as Set (empty, null, singleton, union) import Files (File(..), absolute) import qualified Files (find) import Prelude hiding (lookup) import System.Directory (doesFileExist, withCurrentDirectory) import System.FilePath ((), dropTrailingPathSeparator, takeExtension, takeFileName) type Collection = Map String Article data Blog = Blog { articles :: Collection , name :: String , path :: Path , skin :: Skin , tags :: Map String (Set String) , wording :: Wording } get :: MonadReader Blog m => (Blog -> a) -> m a get = (<$> ask) findArticles :: FilePath -> IO (Map String Article) findArticles = Files.find >=> filterM isMarkDownFile >=> mapM Article.at >=> return . Map.fromList . rights where isMarkDownFile path = do let correctExtension = takeExtension path == ".md" (correctExtension &&) <$> doesFileExist path tagged :: Collection -> 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, Map String (Set String)) discover path = do articles <- findArticles $ articlesPath path 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 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, tags) <- discover path return $ Blog {articles, name, path, skin, tags, wording}