aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Types.hs11
-rw-r--r--site.hs4
2 files changed, 8 insertions, 7 deletions
diff --git a/Types.hs b/Types.hs
index a6a8b2b..12977d8 100644
--- a/Types.hs
+++ b/Types.hs
@@ -6,6 +6,7 @@
module Types where
import Control.Monad.Trans.State.Lazy
+import Data.List.NonEmpty
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Yaml as Y
@@ -44,7 +45,7 @@ data SiteState =
, _templates :: M.Map FilePath Mu.Template
, _outputDir :: FilePath -- ^ Directory for output
, _assetDir :: FilePath -- ^ Directory for output
- , _sourceDir :: FilePath -- ^ Path to page source data
+ , _sourceDirs :: [FilePath] -- ^ Path to page source data
, _templateDir :: FilePath -- ^ Path to template directory
, _defaultTemplate :: FilePath -- ^ Name of the default template
, _redirectTemplate :: FilePath -- ^ Name of the template for redirect pages
@@ -73,12 +74,12 @@ siteOptions' = do
short 'a' <>
help "Assets directory to be copied verbatim" <>
value "assets" <> showDefault
- _sourceDir <-
- strOption $
+ _sourceDirs <-
+ fmap (maybe ["cards"] toList . nonEmpty) . many . strOption $
long "source-directory" <>
short 's' <>
- help "Path to the directory with source data (possibly multiple paths)" <>
- value "cards" <> showDefault
+ help
+ "Path to the directory with source data (possibly multiple paths, defaults to a single directory \"cards\")"
_templateDir <-
strOption $
long "template-directory" <>
diff --git a/site.hs b/site.hs
index 4efe2bd..45bc7b2 100644
--- a/site.hs
+++ b/site.hs
@@ -127,7 +127,7 @@ checkTarget fp = do
-- | Prepend the root path to the given link
rootUrl :: FilePath -> Site FilePath
-rootUrl fp = (</> dropWhile (=='/') fp) <$> use urlBase
+rootUrl fp = (</> dropWhile (== '/') fp) <$> use urlBase
-- | Process a single link pointing out from a page.
processLink :: FilePath -> FilePath -> Site String
@@ -324,7 +324,7 @@ main = do
init <- Options.Applicative.execParser siteOptions
flip runStateT init $ do
installAssets
- use sourceDir >>= sourcePages
+ use sourceDirs >>= traverse sourcePages
sourceTags
use templateDir >>= sourceTemplates
use pages >>= traverse (uncurry installPage) . M.assocs