generalize the options a bit, allow assets from multiple directories

This commit is contained in:
Mirek Kratochvil 2023-10-13 20:45:36 +02:00
parent 4cdbf598c0
commit 5304dd384c
3 changed files with 22 additions and 22 deletions

View file

@ -22,7 +22,6 @@ module Types where
import Control.Monad.Trans.State.Lazy
import qualified Data.ByteString.UTF8
import Data.List.NonEmpty (nonEmpty, toList)
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Yaml as Y
@ -66,7 +65,7 @@ data SiteState =
, _templates :: M.Map FilePath Mu.Template
, _outputDir :: FilePath -- ^ Directory for output
, _searchDataOut :: Maybe FilePath -- ^ File to write the searchable versions of pages to (as JSON)
, _assetDir :: FilePath -- ^ Directory for output
, _assetDirs :: [FilePath] -- ^ Directory for output
, _sourceDirs :: [FilePath] -- ^ Path to page source data
, _notSourceDirs :: [FilePath] -- ^ Subdirectories of source dirs where pages should not be sourced
, _templateDir :: FilePath -- ^ Path to template directory
@ -101,23 +100,21 @@ siteOptions' = do
long "search-data-output" <>
help "Output JSON with searchable page data to this file") <|>
pure Nothing
_assetDir <-
strOption $
_assetDirs <-
many . strOption $
long "assets" <>
short 'a' <>
help "Assets directory to be copied verbatim" <>
value "assets" <> showDefault
help "Assets directory to be copied verbatim (possibly multiple paths)"
_sourceDirs <-
fmap (maybe ["pages"] toList . nonEmpty) . many . strOption $
many . strOption $
long "source-directory" <>
short 's' <>
help
"Path to the directory with source data (possibly multiple paths, defaults to a single directory \"pages\")"
help "Path to the directory with source data (possibly multiple paths)"
_notSourceDirs <-
fmap (maybe ["assets"] toList . nonEmpty) . many . strOption $
many . strOption $
long "exclude-source-directory" <>
help
"Names of subdirectories of the sources that should never be used for sourcing pages (possibly multiple directory names, defaults to a single directory \"assets\")"
"Names of subdirectories of the sources that should never be used for sourcing pages (possibly multiple directory names)"
_templateDir <-
strOption $
long "template-directory" <>
@ -126,7 +123,7 @@ siteOptions' = do
_defaultTemplate <-
strOption $
long "default-template" <>
help "Default template to use for stuff (found in templates directory)" <>
help "Default template to use for stuff (as found in templates directory)" <>
value "default.html" <> showDefault
_redirectTemplate <-
strOption $

View file

@ -3,7 +3,7 @@ cabal-version: 3.0
name: reploy
synopsis: Straightforward static all-in-one website builder
category: Web
version: 0.2.0.0
version: 0.3.0.0
build-type: Simple
license: Apache-2.0
license-file: LICENSE

View file

@ -18,7 +18,7 @@
-- | The main site deployment executable.
module Main where
import Control.Monad ((>=>), filterM, join, unless, when)
import Control.Monad (filterM, join, unless, when)
import Control.Monad.Extra (ifM, whenM)
import Control.Monad.Trans.State.Lazy
import qualified Data.Aeson as AE
@ -333,22 +333,25 @@ installFile fp = do
copy fp file
pure loc
-- | Simply copy a strictly named asset.
installAsset :: FilePath -> Site ()
installAsset fp = do
-- | Simply copy an explicitly named asset in the given asset dir
installAsset :: FilePath -> FilePath -> Site ()
installAsset ad fp = do
od <- use outputDir
ad <- use assetDir
let [src, dst] = map (</> fp) [ad, od]
checkTarget dst
io $ do
putStrLn $ "A -> " ++ src ++ " -> " ++ dst
copy src dst
-- | Copy all files from asset directory.
-- | Copy all files from a given asset directory.
installAssetDir :: FilePath -> Site ()
installAssetDir ad =
io (getRecursiveContents (pure . const False) ad) >>=
traverse_ (installAsset ad)
-- | Copy all files from the asset directories.
installAssets :: Site ()
installAssets =
use assetDir >>=
(io . getRecursiveContents (pure . const False) >=> traverse_ installAsset)
installAssets = use assetdirs >>= traverse installAssetDir
-- | Load tag names from a directory and add them to `tagNames`.
sourceTagnames :: FilePath -> Site ()