actually take args

This commit is contained in:
Mirek Kratochvil 2023-06-08 14:25:32 +02:00
parent 4c1f0f9a4e
commit c6d86aeed3
3 changed files with 66 additions and 20 deletions

View file

@ -1,4 +1,6 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE RecordWildCards #-}
-- | Separated-out main types of the deployment scriptage.
module Types where
@ -8,6 +10,7 @@ import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Yaml as Y
import Lens.Micro.TH
import Options.Applicative
import qualified Text.Mustache as Mu
import qualified Text.Pandoc.Definition
@ -51,23 +54,63 @@ data SiteState =
makeLenses ''SiteState
-- | Make a completely empty `SiteState` for the `Site` monad.
emptySiteState =
SiteState
{ _pages = M.empty
, _redirects = M.empty
, _htags = M.empty
, _installs = S.empty
, _targets = S.empty
, _templates = M.empty
, _outputDir = "_site"
, _assetDir = "assets"
, _defaultTemplate = "default.html"
, _redirectTemplate = "redirect.html"
, _tagTemplate = "tag.html"
, _urlBase = "/"
, _dumpFinalState = False
}
-- | Monad for running the site generator.
type Site a = StateT SiteState IO a
-- | Parser for commandline options
siteOptions' :: Parser SiteState
siteOptions' = do
_outputDir <-
strOption $
long "output" <>
short 'd' <>
help "Directory to render the site to" <> value "_site" <> showDefault
_assetDir <-
strOption $
long "assets" <>
short 'a' <>
help "Assets directory to be copied verbatim" <>
value "assets" <> showDefault
--TODO templates directory!
_defaultTemplate <-
strOption $
long "default-template" <>
help "Default template to use for stuff (found in templates directory)" <>
value "default.html" <> showDefault
_redirectTemplate <-
strOption $
long "redirect-template" <>
help "Template for making redirect pages" <>
value "redirect.html" <> showDefault
_tagTemplate <-
strOption $
long "tag-template" <>
help "Template for making tag-listing pages" <>
value "tag.html" <> showDefault
_urlBase <-
strOption $
long "url-base" <>
short 'u' <> help "Base absolute URL" <> value "/" <> showDefault
_dumpFinalState <-
switch $
long "dump-state" <>
short 'D' <>
help "Print out the complete internal state after the site is built"
pure
SiteState
{ _pages = M.empty
, _redirects = M.empty
, _htags = M.empty
, _installs = S.empty
, _targets = S.empty
, _templates = M.empty
, ..
}
-- | ParserInfo for commandline options
siteOptions =
info
(siteOptions' <**> helper)
(fullDesc <>
progDesc "Build a R3 Cards-like site" <>
header "site - the R3 site builder")

View file

@ -19,6 +19,7 @@ executable site
, microlens-mtl
, microlens-th
, mustache
, optparse-applicative
, pandoc
, pandoc-types
, parsec

View file

@ -36,6 +36,7 @@ import Text.Pandoc.Class (runIOorExplode)
import Text.Pandoc.Readers.Markdown (readMarkdown)
import Text.Pandoc.Writers.HTML (writeHtml5String)
import qualified Text.Parsec.Error
import qualified Options.Applicative
import FormatOpts
import Types
@ -316,8 +317,9 @@ renderTags :: Site ()
renderTags = use (htags . to M.keys) >>= traverse_ renderTag
-- | Build the whole site.
main =
flip runStateT emptySiteState $ do
main = do
init <- Options.Applicative.execParser siteOptions
flip runStateT init $ do
installAssets
traverse sourcePages ["external"]
sourceTags