Compare commits

..

No commits in common. "2eb5e608aca4d439ca7bc5338de8bba6f8b75722" and "f95f2bf2f044379789dfe9f3f7ee34b1dd9d1690" have entirely different histories.

8 changed files with 75 additions and 157 deletions

View file

@ -1,10 +1,13 @@
default:
image: repomanager.lcsb.uni.lu:9999/docker:27.4.0
before_script:
- unset DOCKER_HOST
- docker login -u $CI_REGISTRY_USER -p $CI_REGISTRY_PASSWORD $CI_REGISTRY
tags:
- lcsb
image: docker:20.10.16
variables:
DOCKER_DRIVER: overlay2
DOCKER_TLS_CERTDIR: ""
services:
- name: repomanager.lcsb.uni.lu:9999/library/docker:20.10.16-dind
command: ["--mtu=1458", "--registry-mirror", "https://repomanager.lcsb.uni.lu:9999"]
alias: docker
stages:
- build
@ -12,9 +15,12 @@ stages:
build:
stage: build
script:
- docker build --pull --load -t $CI_REGISTRY_IMAGE:latest .
- docker login -u $CI_REGISTRY_USER -p $CI_REGISTRY_PASSWORD $CI_REGISTRY
- docker build -t $CI_REGISTRY_IMAGE:latest .
- docker push $CI_REGISTRY_IMAGE:latest
- docker tag $CI_REGISTRY_IMAGE:latest $CI_REGISTRY_IMAGE:$CI_COMMIT_SHORT_SHA
- docker push $CI_REGISTRY_IMAGE:$CI_COMMIT_SHORT_SHA
rules:
- if: '$CI_COMMIT_REF_NAME == "master"'
tags:
- lcsb

View file

@ -17,7 +17,7 @@
FROM debian:trixie
RUN apt -y update && apt -y install \
npm nodejs git git-lfs ssh rsync ghc cabal-install build-essential pkg-config zlib1g-dev jq yq \
yarnpkg git git-lfs ssh rsync ghc cabal-install build-essential pkg-config zlib1g-dev jq yq \
&& rm -fr /var/cache/apt
WORKDIR /opt/reploy
@ -31,4 +31,4 @@ WORKDIR /data
COPY assets /data/assets/
COPY templates /data/templates/
COPY pages /data/pages/
ENTRYPOINT ["/root/.local/bin/reploy"]
ENTRYPOINT ["/root/.cabal/bin/reploy"]

View file

@ -20,7 +20,9 @@
-- | Separated-out main types of the deployment scriptage.
module Types where
import AesonUtils
import Control.Monad.Trans.State.Lazy
import qualified Data.ByteString.UTF8
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Yaml as Y
@ -38,14 +40,6 @@ data PageInfo = PageInfo
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`
@ -68,7 +62,6 @@ data SiteState = SiteState
, _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.
@ -88,7 +81,6 @@ siteOptions' = do
strOption
$ long "output"
<> short 'd'
<> metavar "OUTDIR"
<> help "Directory to render the site to"
<> value "_site"
<> showDefault
@ -96,33 +88,28 @@ siteOptions' = do
Just
<$> (strOption
$ long "search-data-output"
<> metavar "JSON"
<> help "Output JSON with searchable page data to this file")
<|> pure Nothing
_assetDirs <-
many . strOption
$ long "assets"
<> short 'a'
<> metavar "DIR"
<> help
"Assets directory to be copied verbatim (possibly multiple paths)"
_sourceDirs <-
many . strOption
$ long "source-directory"
<> short 's'
<> metavar "DIR"
<> help
"Path to the directory with source data (possibly multiple paths)"
_notSourceDirs <-
many . strOption
$ long "exclude-source-directory"
<> metavar "EXCLUDE"
<> 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"
<> metavar "FILENAME"
<> help "Name of files with tag metadata"
<> value "tag-metadata.yml"
<> showDefault
@ -130,13 +117,11 @@ siteOptions' = do
many . strOption
$ long "template-directory"
<> short 't'
<> metavar "DIR"
<> help
"Path to the directory with templates (possibly multiple paths)"
_defaultTemplate <-
strOption
$ long "default-template"
<> metavar "FILENAME"
<> help
"Default template to use for stuff (as found in templates directory)"
<> value "default.html"
@ -144,61 +129,53 @@ siteOptions' = do
_redirectTemplate <-
strOption
$ long "redirect-template"
<> metavar "FILENAME"
<> help "Template for making redirect pages"
<> value "redirect.html"
<> showDefault
_tagTemplate <-
strOption
$ long "tag-template"
<> metavar "FILENAME"
<> help "Template for making category view pages"
<> value "tag.html"
<> showDefault
_listTemplate <-
strOption
$ long "list-template"
<> metavar "FILENAME"
<> help "Template for making tag-listing pages"
<> value "list.html"
<> showDefault
_metadataSuffix <-
strOption
$ long "metadata-suffix"
<> metavar "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'
<> metavar "YAML"
<> 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'
<> metavar "FILE"
<> help
"Extra metadata to add to pages rendering, loaded from a YAML file. May be specified multiple times."
]
_extraMeta <-
let processKeyVal :: String -> Y.Value
processKeyVal opt =
case Y.decodeEither' $ Data.ByteString.UTF8.fromString opt of
Right v -> v
Left err ->
error
$ "cannot parse YAML in --extra-metadata: "
++ Y.prettyPrintParseException err
in fmap (foldl objMerge Y.Null . map processKeyVal) . many . strOption
$ long "extra-metadata"
<> short 'e'
<> help
"Extra metadata to add to pages rendering in YAML format. May be specified multiple times."
_urlBase <-
strOption
$ long "url-base"
<> short 'u'
<> metavar "URL"
<> help "Base absolute URL"
<> value "/"
<> showDefault
_indexFile <-
strOption
$ long "index-filename"
<> metavar "FILENAME"
<> help "Directory index to use for page output."
<> help "Base absolute URL"
<> value "index.html"
<> showDefault
_appendUrlIndex <-
@ -222,7 +199,6 @@ siteOptions' = do
, _installs = S.empty
, _targets = S.empty
, _templates = M.empty
, _extraMeta = Y.Null
, ..
}

View file

@ -10,5 +10,3 @@ timestamp: null
# Well hello there
This site is empty, you can start populating it!
[link test](/?link-test)

View file

@ -1,45 +1,38 @@
cabal-version: 3.0
name: reploy
synopsis: Straightforward static all-in-one website builder
category: Web
version: 0.3.3.0
build-type: Simple
license: Apache-2.0
license-file: LICENSE
cabal-version: 3.0
name: reploy
synopsis: Straightforward static all-in-one website builder
category: Web
version: 0.3.2.0
build-type: Simple
license: Apache-2.0
license-file: LICENSE
executable reploy
main-is: reploy.hs
other-modules:
AesonUtils
FormatOpts
Tags
Types
Utils
build-depends:
, aeson ^>=2.1 || ^>=2.2
, base >=4 && <5
, bytestring
, containers
, data-default
, directory
, extra
, filepath
, microlens
, microlens-aeson
, microlens-mtl
, microlens-th
, mustache
, optparse-applicative
, pandoc
, pandoc-types
, parsec
, scientific
, SHA
, text
, transformers
, utf8-string
, yaml
other-modules: Types, AesonUtils, Utils, Tags, FormatOpts
build-depends: base == 4.*
, aeson ^>= 2.1
, bytestring
, containers
, data-default
, directory
, extra
, filepath
, microlens
, microlens-aeson
, microlens-mtl
, microlens-th
, mustache
, optparse-applicative
, pandoc
, pandoc-types
, parsec
, scientific
, SHA
, text
, transformers
, utf8-string
, yaml
ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wunused-imports
default-language: Haskell2010

View file

@ -26,7 +26,6 @@ import qualified Data.Aeson as AE
import qualified Data.Aeson.Key as K
import qualified Data.Aeson.KeyMap as KM
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.UTF8
import Data.Digest.Pure.SHA (sha256, showDigest)
import Data.Foldable (traverse_)
import Data.List (inits, nub, sort)
@ -47,7 +46,6 @@ import System.FilePath
( isAbsolute
, joinPath
, splitFileName
, splitPath
, takeDirectory
, takeFileName
)
@ -177,25 +175,14 @@ rootedLink :: FilePath -> Site FilePath
rootedLink = (<*>) rootedLink' . pure
-- | Process a single link pointing out from a page.
processLink :: FilePath -> FilePath -> FilePath -> Site String
processLink base mount l
| any (l `hasUriScheme`) ["http", "https", "ftp", "mailto"] || take 1 l == "#" =
pure l
| isAbsolute l =
let (path, rest) = break (`elem` ['?', '#']) l
in (<> rest) <$> rootedPageLink path
| l `hasUriScheme` "mount" =
let (path, rest) = break (`elem` ['?', '#']) $ drop 6 l
mountpath =
joinPath . reverse
$ foldl interpretPath (reverse $ splitPath mount) (splitPath path)
interpretPath m x
| x `elem` ["..", "../"] = drop 1 m
| x `elem` [".", "./"] = m
| x == "/" = ["/"]
| otherwise = x : m
in (<> rest) <$> rootedPageLink mountpath
| otherwise = installFile (base </> l) >>= rootedLink
processLink :: FilePath -> FilePath -> Site String
processLink base l =
if any (l `hasUriScheme`) ["http", "https", "ftp", "mailto"]
|| take 1 l == "#"
then pure l
else if isAbsolute l
then rootedPageLink l
else installFile (base </> l) >>= rootedLink
-- | Conjure a function that finds a displayable name for a page at a particular mount.
pageName' :: Site (FilePath -> String)
@ -221,8 +208,6 @@ addGlobalMeta meta = do
rt <- rootedLink'
rtp <- rootedPageLink'
pn <- pageName'
aui <- use appendUrlIndex
ifi <- use indexFile
Y.Object m <- (`objMerge` meta) <$> use extraMeta
let l = map (\(k, v) -> (K.toText k, Mu.toMustache v)) $ KM.toList m
pure . Mu.object
@ -232,9 +217,6 @@ addGlobalMeta meta = do
, ("pageLink", Mu.overText $ T.pack . rtp . T.unpack)
, ("pageName", Mu.overText $ T.pack . pn . T.unpack)
]
++ (if aui
then [("indexFile", Mu.toMustache $ T.pack ifi)]
else [])
-- | Get the expected timestamp file for a given filepath
metadataFile :: FilePath -> Site FilePath
@ -302,8 +284,7 @@ installPage mount pi = do
templ <- use $ templates . to (M.! fromString tname)
file <- indexFilename mount
fixedUrlDoc <-
walkURLs (processLink (pi ^. pagePath . to takeDirectory) mount)
$ pi ^. pageDoc
walkURLs (processLink $ pi ^. pagePath . to takeDirectory) $ pi ^. pageDoc
checkTarget file
body <-
io . runIOorExplode
@ -512,37 +493,10 @@ renderSearchData = use searchDataOut >>= traverse_ go
putStrLn $ "S -> " ++ out
AE.encodeFile out $ Y.array (concat ps)
-- | Souce extra metadata accordingly to the metadata specifications
sourceExtraMetadata :: Site ()
sourceExtraMetadata = do
use extraMetaSpec
>>= fmap (foldl objMerge Y.Null) . traverse loadSpec
>>= assign extraMeta
where
loadSpec :: MetaSpec -> Site Y.Value
loadSpec (MetaSpecInline yaml) =
case Y.decodeEither' $ Data.ByteString.UTF8.fromString yaml of
Right v -> pure v
Left err ->
error
$ "cannot parse extra metadata from inline YAML: "
++ Y.prettyPrintParseException err
loadSpec (MetaSpecFile path) = do
res <- io $ Y.decodeFileEither path
case res of
Right v -> pure v
Left err ->
error
$ "cannot load YAML metadata from "
++ path
++ ": "
++ Y.prettyPrintParseException err
-- | Build the whole site.
main = do
init <- Options.Applicative.execParser siteOptions
flip runStateT init $ do
sourceExtraMetadata
installAssets
use sourceDirs >>= traverse sourcePages
use sourceDirs >>= traverse sourceTagMeta

View file

@ -1,10 +1,4 @@
<header>
{{?menu_items}}Menu:
<ul>
{{#menu_items}}<li>{{.}}</li>{{/menu_items}}
</ul>
{{/menu_items}}
Navigation:
<ul>
<li><a href="{{#pageLink}}/{{/pageLink}}">{{#pageName}}/{{/pageName}}</a></li>

View file

@ -1,3 +0,0 @@
menu_items:
- item1
- item2