68 lines
2.1 KiB
Haskell
68 lines
2.1 KiB
Haskell
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
-- | Separated-out main types of the deployment scriptage.
|
|
module Types where
|
|
|
|
import Control.Monad.Trans.State.Lazy
|
|
import qualified Data.Map as M
|
|
import qualified Data.Set as S
|
|
import qualified Data.Yaml as Y
|
|
import Lens.Micro.TH
|
|
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]
|
|
-- | 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
|
|
, _assetDir :: FilePath -- ^ Directory for output
|
|
, _defaultTemplate :: FilePath -- ^ Name of the default template
|
|
, _redirectTemplate :: FilePath -- ^ Name of the template for redirect pages
|
|
}
|
|
deriving (Show)
|
|
|
|
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"
|
|
}
|
|
|
|
-- | Monad for running the site generator.
|
|
type Site a = StateT SiteState IO a
|