Remove the option to generate into a directory other than the parent directory of the one containing the articles to get rid of the hassle of copying the markdown sources and simplify working with relative URLs during the generation process

This commit is contained in:
Tissevert 2019-01-29 23:08:38 +01:00
parent 0ca01da4d3
commit a8fd44e7ac
5 changed files with 42 additions and 70 deletions

View File

@ -1,34 +1,21 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
module Arguments ( module Arguments (
Arguments(..) Arguments(..)
, Configuration , configuration
, getConfiguration
) where ) where
import Options.Applicative import Options.Applicative
import System.FilePath.Posix (dropTrailingPathSeparator, isValid, takeDirectory, takeFileName) import System.FilePath.Posix (dropTrailingPathSeparator, isValid)
--import System.Directory (doesDirectoryExist)
data Arguments a b = Arguments { data Arguments = Arguments {
sourceDir :: FilePath sourceDir :: FilePath
, outputDir :: a , blogName :: Maybe String
, blogName :: b , previewCountArg :: Int
, previewCount :: Int
} }
type InputArguments = Arguments (Maybe FilePath) (Maybe String) arguments :: Parser Arguments
type Configuration = Arguments FilePath String
arguments :: Parser InputArguments
arguments = Arguments arguments = Arguments
<$> argument directory (metavar "INPUT_DIR") <$> argument directory (metavar "INPUT_DIR")
<*> option (optional directory) (
metavar "OUTPUT_DIR"
<> value Nothing
<> short 'o'
<> long "output"
<> help "directory in which to generate the blog"
)
<*> option (optional str) ( <*> option (optional str) (
metavar "BLOG_NAME" metavar "BLOG_NAME"
<> value Nothing <> value Nothing
@ -44,29 +31,15 @@ arguments = Arguments
<> help "number of articles listed on the page of each category" <> help "number of articles listed on the page of each category"
) )
{-
existingDirectory :: ReadM FilePath
existingDirectory = eitherReader $ \path ->
if doesDirectoryExist path
then Right path
else Left "The input directory must be an existing path"
-}
directory :: ReadM FilePath directory :: ReadM FilePath
directory = eitherReader $ \path -> directory = eitherReader $ \path ->
if isValid path if isValid path
then Right $ dropTrailingPathSeparator path then Right $ dropTrailingPathSeparator path
else Left "This string doesn't represent a valid path" else Left "This string doesn't represent a valid path"
getConfiguration :: IO Configuration configuration :: IO Arguments
getConfiguration = do configuration =
invocation <- execParser $ execParser $
info (arguments <**> helper) info (arguments <**> helper)
( fullDesc ( fullDesc
) )
let outputDirOrDefault = maybe (takeDirectory $ sourceDir invocation) id (outputDir invocation)
let blogNameOrDefault = maybe (takeFileName outputDirOrDefault) id (blogName invocation)
return $ invocation {
outputDir = outputDirOrDefault
, blogName = blogNameOrDefault
}

View File

@ -5,16 +5,15 @@ module Blog (
, get , get
) where ) where
import Arguments (Arguments(..), Configuration) import Arguments (Arguments(..))
import Control.Monad ((>=>), filterM, forM) import Control.Monad ((>=>), filterM, forM)
import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader (MonadReader(..), ReaderT)
import Data.Map (Map) import Data.Map (Map)
import qualified Data.Map as Map (fromList, member) import qualified Data.Map as Map (fromList, member)
import Data.Set (Set) import Data.Set (Set)
import qualified Data.Set as Set (empty, null, singleton, union) import qualified Data.Set as Set (empty, null, singleton, union)
import System.Directory (doesFileExist, listDirectory) import System.Directory (doesFileExist, listDirectory)
import System.FilePath.Posix ((</>), takeExtension, takeFileName) import System.FilePath.Posix ((</>), takeExtension, takeDirectory, takeFileName)
import System.Posix.Types (FileID) import System.Posix.Types (FileID)
import System.Posix.Files (FileStatus, getFileStatus, fileID) import System.Posix.Files (FileStatus, getFileStatus, fileID)
@ -28,6 +27,8 @@ type Collection = Map FileID Article
data Blog = Blog { data Blog = Blog {
articles :: Collection articles :: Collection
, name :: String , name :: String
, previewCount :: Int
, root :: FilePath
, tags :: Map String (Set FileID) , tags :: Map String (Set FileID)
} }
@ -62,11 +63,11 @@ tagged collection path = do
else return Set.empty else return Set.empty
return (takeFileName path, foldl Set.union Set.empty fileIDs) return (takeFileName path, foldl Set.union Set.empty fileIDs)
get :: ReaderT Configuration IO Blog get :: Arguments -> IO Blog
get = do get (Arguments {sourceDir, blogName, previewCountArg}) = do
path <- sourceDir <$> ask let root = takeDirectory sourceDir
articles <- findArticles path let name = maybe (takeFileName root) id $ blogName
name <- blogName <$> ask articles <- findArticles sourceDir
tags <- Map.fromList . filter (not . Set.null . snd) tags <- Map.fromList . filter (not . Set.null . snd)
<$> (find (path </> "tags") >>= mapM (articles `tagged`)) <$> (find (sourceDir </> "tags") >>= mapM (articles `tagged`))
return $ Blog { articles , name, tags } return $ Blog { articles , name, previewCount = previewCountArg, root, tags }

View File

@ -4,7 +4,6 @@ module Dom (
generate generate
) where ) where
import Arguments (Arguments(..), Configuration)
import Blog (Article(..), Blog(..)) import Blog (Article(..), Blog(..))
import Control.Monad (forM_) import Control.Monad (forM_)
import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.IO.Class (MonadIO(..))
@ -61,15 +60,15 @@ render (Page {category, full, articlesFeatured}) blog =
pageTitle = pageTitle =
if full then "All" else "Latest" ++ " articles" ++ maybe "" (" tagged " ++) category if full then "All" else "Latest" ++ " articles" ++ maybe "" (" tagged " ++) category
generateCollection :: (Maybe String, FilePath, [Article]) -> Blog -> ReaderT Configuration IO () generateCollection :: (Maybe String, FilePath, [Article]) -> ReaderT Blog IO ()
generateCollection (_, _, []) _ = return () generateCollection (_, _, []) = return ()
generateCollection (category, path, articlesFeatured) blog = do generateCollection (category, path, articlesFeatured) = do
n <- previewCount <$> ask blog <- ask
liftIO $ createDirectoryIfMissing False path liftIO $ createDirectoryIfMissing False path
forM_ (pages n) $ \page -> forM_ (pages $ previewCount blog) $ \page ->
liftIO $ renderToFile (urlPath page) (render page blog) liftIO $ renderToFile (urlPath page) (render page blog)
where where
pages n = [ pages articlesCount = [
Page { Page {
category category
, full = True , full = True
@ -80,16 +79,16 @@ generateCollection (category, path, articlesFeatured) blog = do
category category
, full = False , full = False
, urlPath = path </> "index.html" , urlPath = path </> "index.html"
, articlesFeatured = take n articlesFeatured , articlesFeatured = take articlesCount articlesFeatured
} }
] ]
generate :: Blog -> ReaderT Configuration IO () generate :: ReaderT Blog IO ()
generate blog@(Blog {articles, tags}) = do generate = do
path <- outputDir <$> ask Blog {root, articles, tags} <- ask
generateCollection (Nothing, path, sortByDate $ Map.elems articles) blog generateCollection (Nothing, root, sortByDate $ Map.elems articles)
forM_ (Map.toList tags) $ \(tag, tagged) -> forM_ (Map.toList $ tags) $ \(tag, tagged) ->
generateCollection (Just tag, path </> tag, sortByDate $ getArticles tagged) blog generateCollection (Just tag, root </> tag, sortByDate $ getArticles tagged articles)
where where
getArticles tagged = Map.elems $ Map.filterWithKey (\k _ -> Set.member k tagged) articles getArticles tagged = Map.elems . Map.filterWithKey (\k _ -> Set.member k tagged)
sortByDate = sortOn (Down . modificationTime . fileStatus) sortByDate = sortOn (Down . modificationTime . fileStatus)

View File

@ -2,7 +2,6 @@ module JSON (
generate generate
) where ) where
import Arguments (Arguments(..), Configuration)
import Blog (Blog(..)) import Blog (Blog(..))
import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader (MonadReader(..), ReaderT) import Control.Monad.Reader (MonadReader(..), ReaderT)
@ -11,7 +10,7 @@ import Data.ByteString.Lazy (writeFile)
import System.FilePath.Posix ((</>)) import System.FilePath.Posix ((</>))
import Prelude hiding (writeFile) import Prelude hiding (writeFile)
generate :: Blog -> ReaderT Configuration IO () generate :: ReaderT Blog IO ()
generate _ = do generate = do
path <- outputDir <$> ask path <- root <$> ask
liftIO $ writeFile (path </> "articles.json") (encode $ object []) liftIO $ writeFile (path </> "articles.json") (encode $ object [])

View File

@ -1,7 +1,7 @@
{- LANGUAGE NamedFieldPuns #-} {- LANGUAGE NamedFieldPuns #-}
module Main where module Main where
import Arguments (getConfiguration) import Arguments (configuration)
import qualified Blog (get) import qualified Blog (get)
import qualified Dom (generate) import qualified Dom (generate)
import qualified JSON (generate) import qualified JSON (generate)
@ -9,9 +9,9 @@ import Control.Monad.Reader (runReaderT)
main :: IO () main :: IO ()
main = do main = do
getConfiguration configuration
>>= Blog.get
>>= runReaderT (do >>= runReaderT (do
blog <- Blog.get Dom.generate
Dom.generate blog JSON.generate
JSON.generate blog
) )