aboutsummaryrefslogtreecommitdiff
path: root/Types.hs
blob: e818c63c9549379e322244b226c1b893f85a9297 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE RecordWildCards #-}

-- | 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 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]
    -- | 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
    , _tagTemplate :: FilePath -- ^ Name of the template for tag 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
  _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")