source multiple directories at once
This commit is contained in:
parent
3d805c5d80
commit
2b68087b23
11
Types.hs
11
Types.hs
|
@ -6,6 +6,7 @@
|
||||||
module Types where
|
module Types where
|
||||||
|
|
||||||
import Control.Monad.Trans.State.Lazy
|
import Control.Monad.Trans.State.Lazy
|
||||||
|
import Data.List.NonEmpty
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import qualified Data.Yaml as Y
|
import qualified Data.Yaml as Y
|
||||||
|
@ -44,7 +45,7 @@ data SiteState =
|
||||||
, _templates :: M.Map FilePath Mu.Template
|
, _templates :: M.Map FilePath Mu.Template
|
||||||
, _outputDir :: FilePath -- ^ Directory for output
|
, _outputDir :: FilePath -- ^ Directory for output
|
||||||
, _assetDir :: 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
|
, _templateDir :: FilePath -- ^ Path to template directory
|
||||||
, _defaultTemplate :: FilePath -- ^ Name of the default template
|
, _defaultTemplate :: FilePath -- ^ Name of the default template
|
||||||
, _redirectTemplate :: FilePath -- ^ Name of the template for redirect pages
|
, _redirectTemplate :: FilePath -- ^ Name of the template for redirect pages
|
||||||
|
@ -73,12 +74,12 @@ siteOptions' = do
|
||||||
short 'a' <>
|
short 'a' <>
|
||||||
help "Assets directory to be copied verbatim" <>
|
help "Assets directory to be copied verbatim" <>
|
||||||
value "assets" <> showDefault
|
value "assets" <> showDefault
|
||||||
_sourceDir <-
|
_sourceDirs <-
|
||||||
strOption $
|
fmap (maybe ["cards"] toList . nonEmpty) . many . strOption $
|
||||||
long "source-directory" <>
|
long "source-directory" <>
|
||||||
short 's' <>
|
short 's' <>
|
||||||
help "Path to the directory with source data (possibly multiple paths)" <>
|
help
|
||||||
value "cards" <> showDefault
|
"Path to the directory with source data (possibly multiple paths, defaults to a single directory \"cards\")"
|
||||||
_templateDir <-
|
_templateDir <-
|
||||||
strOption $
|
strOption $
|
||||||
long "template-directory" <>
|
long "template-directory" <>
|
||||||
|
|
4
site.hs
4
site.hs
|
@ -127,7 +127,7 @@ checkTarget fp = do
|
||||||
|
|
||||||
-- | Prepend the root path to the given link
|
-- | Prepend the root path to the given link
|
||||||
rootUrl :: FilePath -> Site FilePath
|
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.
|
-- | Process a single link pointing out from a page.
|
||||||
processLink :: FilePath -> FilePath -> Site String
|
processLink :: FilePath -> FilePath -> Site String
|
||||||
|
@ -324,7 +324,7 @@ main = do
|
||||||
init <- Options.Applicative.execParser siteOptions
|
init <- Options.Applicative.execParser siteOptions
|
||||||
flip runStateT init $ do
|
flip runStateT init $ do
|
||||||
installAssets
|
installAssets
|
||||||
use sourceDir >>= sourcePages
|
use sourceDirs >>= traverse sourcePages
|
||||||
sourceTags
|
sourceTags
|
||||||
use templateDir >>= sourceTemplates
|
use templateDir >>= sourceTemplates
|
||||||
use pages >>= traverse (uncurry installPage) . M.assocs
|
use pages >>= traverse (uncurry installPage) . M.assocs
|
||||||
|
|
Loading…
Reference in a new issue