Add two arguments to pass HTML files for the head and the banner of pages

This commit is contained in:
Tissevert 2019-02-02 17:26:07 +01:00
parent a9f220f9d8
commit f81776d3de
2 changed files with 49 additions and 18 deletions

View File

@ -1,12 +1,12 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
module Arguments ( module Arguments (
Arguments(..) Arguments(..)
, configuration , get
) where ) where
import Data.Monoid ((<>)) import Data.Monoid ((<>))
import Options.Applicative import Options.Applicative
import System.Directory (doesDirectoryExist, makeAbsolute) import System.Directory (doesDirectoryExist, doesFileExist, makeAbsolute)
import System.Exit (die) import System.Exit (die)
import System.FilePath.Posix (dropTrailingPathSeparator, isValid) import System.FilePath.Posix (dropTrailingPathSeparator, isValid)
@ -14,11 +14,13 @@ data Arguments = Arguments {
sourceDir :: FilePath sourceDir :: FilePath
, blogName :: Maybe String , blogName :: Maybe String
, previewCountArg :: Int , previewCountArg :: Int
, bannerPath :: Maybe FilePath
, headPath :: Maybe FilePath
} }
arguments :: Parser Arguments parseArguments :: Parser Arguments
arguments = Arguments parseArguments = Arguments
<$> argument directory (metavar "INPUT_DIR") <$> argument filePath (metavar "INPUT_DIR")
<*> option (optional str) ( <*> option (optional str) (
metavar "BLOG_NAME" metavar "BLOG_NAME"
<> value Nothing <> value Nothing
@ -33,19 +35,48 @@ arguments = Arguments
<> long "preview-count" <> long "preview-count"
<> help "number of articles listed on the page of each category" <> help "number of articles listed on the page of each category"
) )
<*> option (optional filePath) (
metavar "BANNER_PATH"
<> value Nothing
<> short 'b'
<> long "banner"
<> help "path to the file to use for the blog's banner"
)
<*> option (optional filePath) (
metavar "HEAD_PATH"
<> value Nothing
<> short 'H'
<> long "head"
<> help "path to the file to add in the blog's head"
)
directory :: ReadM FilePath filePath :: ReadM FilePath
directory = eitherReader $ \path -> filePath = 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"
configuration :: IO Arguments ifNotDie :: (a -> IO Bool) -> (a -> String) -> a -> IO ()
configuration = do ifNotDie check messageBuilder input = do
inputArguments <- execParser $ info (arguments <**> helper) fullDesc bool <- check input
directoryExists <- doesDirectoryExist $ sourceDir inputArguments if bool
if directoryExists then return ()
then do else die $ messageBuilder input
absolutePath <- makeAbsolute $ sourceDir inputArguments
return $ inputArguments { sourceDir = absolutePath } get :: IO Arguments
else die "INPUT_DIR doesn't exist" get = do
arguments <- execParser $ info (parseArguments <**> helper) fullDesc
doesDirectoryExist `ifNotDie` noSuchDirectory $ sourceDir arguments
absoluteSourceDir <- makeAbsolute $ sourceDir arguments
mapM_ (doesFileExist `ifNotDie` noSuchFile) $ bannerPath arguments
absoluteBannerPath <- mapM makeAbsolute $ bannerPath arguments
mapM_ (doesFileExist `ifNotDie` noSuchFile) $ headPath arguments
absoluteHeadPath <- mapM makeAbsolute $ headPath arguments
return $ arguments {
sourceDir = absoluteSourceDir
, bannerPath = absoluteBannerPath
, headPath = absoluteHeadPath
}
where
noSuchDirectory = (++ ": no such directory")
noSuchFile = (++ ": no such file")

View File

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