aboutsummaryrefslogtreecommitdiff
path: root/Types.hs
blob: 78f0013b41427ef894eaa5317d74c6a33f3d8aab (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
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
{-
 - Copyright (C) 2023 University of Luxembourg
 -
 - Licensed under the Apache License, Version 2.0 (the "License"); you may not
 - use this file except in compliance with the License. You may obtain a copy
 - of the License from the LICENSE file in this repository, or at:
 -
 - http://www.apache.org/licenses/LICENSE-2.0
 -
 - Unless required by applicable law or agreed to in writing, software
 - distributed under the License is distributed on an "AS IS" BASIS, WITHOUT
 - WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. See the
 - License for the specific language governing permissions and limitations
 - under the License.
 -}
{-# 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

-- | Information about where to source all extra metadata
data MetaSpec
  = MetaSpecInline String
  | MetaSpecFile FilePath
  deriving (Show)

makeLenses ''MetaSpec

-- | Complete internal state of the deployment process that holds all data
data SiteState = SiteState
  { _pages :: M.Map FilePath PageInfo -- ^ Map of page mounts to `PageInfo`
  , _redirects :: M.Map FilePath FilePath -- ^ Map of redirects (from -> to)
  , _htags :: M.Map [String] [FilePath] -- ^ Map of tags, assigning to each tag sequence a list of tagged page mounts
  , _ehtags :: 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).
  , _tagMeta :: M.Map [String] Y.Value -- ^ Map of tags to expanded human-friendly names
  , _installs :: S.Set (String, FilePath) -- ^ List of copy-installed files (among other, this enables sharing)
  , _targets :: S.Set FilePath -- ^ List of files installed to the target site (this allows us to throw an error in case anything would write to the same target twice)
  , _templates :: M.Map FilePath Mu.Template -- ^ Map of Mustache templates organized by template search path (within the template directory)
  , _outputDir :: FilePath -- ^ Directory for output
  , _searchDataOut :: Maybe FilePath -- ^ File to write the searchable versions of pages to (as JSON)
  , _assetDirs :: [FilePath] -- ^ Directory for output
  , _sourceDirs :: [FilePath] -- ^ Path to page source data
  , _notSourceDirs :: [FilePath] -- ^ Subdirectories of source dirs where pages should not be sourced
  , _tagMetaFile :: FilePath -- ^ Name of the "tag metadata" files to find in the source directories.
  , _templateDirs :: [FilePath] -- ^ Paths to template directories
  , _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
  , _extraMeta :: Y.Value -- ^ Extra metadata added to rendering of all templates
  , _extraMetaSpec :: [MetaSpec] -- ^ sources for the extra metadata
  , _metadataSuffix :: FilePath -- ^ File suffix to search for a extra metadata (e.g., if the suffix is ".extra", the extra metadata for file "page.md" will be looked for in "page.md.extra"). These are best autogenerated with a script that sources the data from git or so.
  , _indexFile :: FilePath -- ^ Name of the "index" files to be generated.
  , _urlBase :: FilePath -- ^ "Root route" to prepend to all absolute links.
  , _appendUrlIndex :: Bool -- ^ Append full index filenames to all page URLs
  , _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
  _assetDirs <-
    many . strOption
      $ long "assets"
          <> short 'a'
          <> help
               "Assets directory to be copied verbatim (possibly multiple paths)"
  _sourceDirs <-
    many . strOption
      $ long "source-directory"
          <> short 's'
          <> help
               "Path to the directory with source data (possibly multiple paths)"
  _notSourceDirs <-
    many . strOption
      $ long "exclude-source-directory"
          <> help
               "Names of subdirectories of the sources that should never be used for sourcing pages (possibly multiple directory names)"
  _tagMetaFile <-
    strOption
      $ long "tag-metadata-file"
          <> help "Name of files with tag metadata"
          <> value "tag-metadata.yml"
          <> showDefault
  _templateDirs <-
    many . strOption
      $ long "template-directory"
          <> short 't'
          <> help
               "Path to the directory with templates (possibly multiple paths)"
  _defaultTemplate <-
    strOption
      $ long "default-template"
          <> help
               "Default template to use for stuff (as 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
  _metadataSuffix <-
    strOption
      $ long "metadata-suffix"
          <> help
               "Suffix for YAML files with base metadata for each markdown page. Metadata from files override the extra metadata specified on commandline, but are overridden by metadata specified directly in the markdown header of the pages."
          <> value ".metadata.yml"
          <> showDefault
  _extraMetaSpec <-
    many
      $ asum
          [ fmap MetaSpecInline . strOption
              $ long "extra-metadata"
                  <> short 'e'
                  <> help
                       "Extra metadata to add to pages rendering in YAML format. May be specified multiple times."
          , fmap MetaSpecFile . strOption
              $ long "extra-metadata-file"
                  <> short 'E'
                  <> help
                       "Extra metadata to add to pages rendering, loaded from a YAML file. May be specified multiple times."
          ]
  _urlBase <-
    strOption
      $ long "url-base"
          <> short 'u'
          <> help "Base absolute URL"
          <> value "/"
          <> showDefault
  _indexFile <-
    strOption
      $ long "index-filename"
          <> help "Base absolute URL"
          <> value "index.html"
          <> showDefault
  _appendUrlIndex <-
    switch
      $ long "append-url-index"
          <> help
               "Append 'index.html' to all urls, negating server problems with directory index settings."
  _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
      , _tagMeta = M.empty
      , _installs = S.empty
      , _targets = S.empty
      , _templates = M.empty
      , _extraMeta = Y.Null
      , ..
      }

-- | ParserInfo for commandline options
siteOptions =
  info
    (siteOptions' <**> helper)
    (fullDesc
       <> progDesc "Build a R3 static site"
       <> header "reploy - the R3 static site builder")