{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE RecordWildCards #-} -- | Separated-out main types of the deployment scriptage. 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 import Lens.Micro.TH import Options.Applicative import qualified Text.Mustache as Mu import qualified Text.Pandoc.Definition -- | Information about a single deployed page (with metadata etc). data PageInfo = PageInfo { _pagePath :: FilePath -- ^ original path to the markdown file , _pageMeta :: Y.Value -- ^ YAML metadata extracted from the file , _pageDoc :: Text.Pandoc.Definition.Pandoc -- ^ Page data } deriving (Show) makeLenses ''PageInfo -- | Complete internal state of the deployment process that holds all data data SiteState = SiteState -- | Map of page mounts to `PageInfo` { _pages :: M.Map FilePath PageInfo -- | Map of redirects (from -> to) , _redirects :: M.Map FilePath FilePath -- | Map of tags, assigning to each tag sequence a list of -- tagged page mounts , _htags :: M.Map [String] [FilePath] -- | Map of tags, assigning to each tag sequence a list of tagged page -- mounts. This one is expanded (tags imply parent categories). , _ehtags :: M.Map [String] [FilePath] -- | List of installed files (enables sharing) , _installs :: S.Set (String, FilePath) -- | List of installed files (prevents overwriting) , _targets :: S.Set FilePath -- | Map of Mustache templates organized by template search path (within -- the template directory) , _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 , _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 , _tagTemplate :: FilePath -- ^ Name of the template for category pages , _listTemplate :: FilePath -- ^ Name of the template for listing pages , _urlBase :: FilePath -- ^ "Root route" to prepend to all absolute links. , _dumpFinalState :: Bool -- ^ Triggers printing out the structure when the processing finishes. } deriving (Show) makeLenses ''SiteState -- | 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 _searchDataOut <- Just <$> (strOption $ long "search-data-output" <> help "Output JSON with searchable page data to this file") <|> pure Nothing _assetDir <- strOption $ long "assets" <> short 'a' <> help "Assets directory to be copied verbatim" <> value "assets" <> showDefault _sourceDirs <- fmap (maybe ["cards"] toList . nonEmpty) . many . strOption $ long "source-directory" <> short 's' <> help "Path to the directory with source data (possibly multiple paths, defaults to a single directory \"cards\")" _templateDir <- strOption $ long "template-directory" <> help "Path to the directory with templates" <> value "templates" <> showDefault _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 category view pages" <> value "tag.html" <> showDefault _listTemplate <- strOption $ long "list-template" <> help "Template for making tag-listing pages" <> value "list.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 , _ehtags = 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")