{-# LANGUAGE CPP #-} module Arguments ( Arguments(..) , get ) where #if !MIN_VERSION_base(4,11,0) import Data.Monoid ((<>)) #endif import Data.Version (showVersion) import Control.Applicative ((<|>), (<**>), optional) import Options.Applicative ( Parser, ReadM, argument, auto, eitherReader, execParser, flag', fullDesc , header, help, helper, info, long, metavar, short, str, switch, value ) import qualified Options.Applicative as Optparse (option) import qualified Paths_hablo as Hablo (version) import System.FilePath (dropTrailingPathSeparator, isValid) data Arguments = BlogConfig { sourceDir :: FilePath , articlesPath :: Maybe FilePath , bannerPath :: Maybe FilePath , cardImage :: Maybe FilePath , commentsURL :: Maybe String , favicon :: Maybe FilePath , headPath :: Maybe FilePath , name :: Maybe String , openGraphCards :: Bool , pagesPath :: Maybe FilePath , previewArticlesCount :: Int , previewLinesCount :: Int , remarkableConfig :: Maybe FilePath , rss :: Bool , siteURL :: Maybe String , wording :: Maybe FilePath } | Version option :: ReadM a -> Char -> String -> String -> String -> Parser (Maybe a) option readM aShort aLong aMetavar aHelpMessage = Optparse.option (optional readM) ( metavar aMetavar <> value Nothing <> short aShort <> long aLong <> help aHelpMessage ) blogConfig :: Parser Arguments blogConfig = BlogConfig <$> argument filePath (value "." <> metavar "INPUT_DIR") <*> option filePath 'a' "articles" "DIRECTORY" "relative path to the directory containing the articles within INPUT_DIR" <*> option filePath 'b' "banner" "FILE" "path to the file to use for the blog's banner" <*> option filePath 'c' "card-image" "FILE" "relative path to the image to use for the blog's card" <*> option filePath 'C' "comments-url" "URL" "URL of the instance where comments are stored" <*> option filePath 'f' "favicon" "FILE" "path to the image to use for the blog's favicon" <*> option filePath 'H' "head" "FILE" "path to the file to add in the blog's head" <*> option str 'n' "name" "BLOG_NAME" "name of the blog" <*> switch (short 'O' <> long "open-graph-cards" <> help "enable Open Graph cards") <*> option filePath 'p' "pages" "DIRECTORY" "relative path to the directory containing the pages within INPUT_DIR" <*> Optparse.option auto ( metavar "INTEGER" <> value 3 <> short 'A' <> long "preview-articles" <> help "number of articles listed on the page of each category" ) <*> Optparse.option auto ( metavar "INTEGER" <> value 10 <> short 'L' <> long "preview-lines" <> help "number of lines to display in articles preview" ) <*> option filePath 'r' "remarkable-config" "FILE" "path to a file containing a custom RemarkableJS configuration" <*> switch (short 'R' <> long "rss" <> help "enable RSS feeds generation") <*> option filePath 'u' "site-url" "URL" "URL where the blog is published" <*> option filePath 'w' "wording" "FILE" "path to the file containing the wording to use" version :: Parser Arguments version = flag' Version ( long "version" <> short 'v' <> help "print the version number" ) arguments :: Parser Arguments arguments = blogConfig <|> version filePath :: ReadM FilePath filePath = eitherReader $ \path -> if isValid path then Right $ dropTrailingPathSeparator path else Left "This string doesn't represent a valid path" get :: IO Arguments get = do execParser $ info (arguments <**> helper) (fullDesc <> header ("Hablo v" ++ showVersion Hablo.version))