Skip to content

Commit

Permalink
Merge branch 'develop' into dependabot/npm_and_yarn/develop/fortaweso…
Browse files Browse the repository at this point in the history
…me/free-solid-svg-icons-6.4.2
  • Loading branch information
falgon authored Sep 7, 2023
2 parents 18cca92 + 4b8b54b commit bdaae33
Show file tree
Hide file tree
Showing 42 changed files with 1,063 additions and 498 deletions.
55 changes: 35 additions & 20 deletions app/site/Main.hs
Original file line number Diff line number Diff line change
@@ -1,29 +1,28 @@
{-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
module Main (main) where

import Control.Monad.Reader (ReaderT (..))
import Data.Foldable (fold)
import Data.String (fromString)
import qualified Data.Text.Lazy as TL
import Data.Version (showVersion)
import Development.GitRev (gitHash)
import Hakyll
import qualified Options.Applicative as OA
import qualified Paths_roki_web as P
import System.FilePath (joinPath)

import Config (hakyllConfig, siteName,
writerOptions, writerPreviewOptions)
import qualified Config.Blog as B
import qualified Config.Blogs.AnotherBlog as AB
import qualified Config.Blogs.TechBlog as TB
import Config.RegexUtils (intercalateDir)
import qualified Contexts.Field.RokiDiary as RokiDiary
import qualified Contexts.Field.RokiLog as RokiLog
import Lucid.Base (renderText)
import qualified Rules.Blog as B
import qualified Rules.IndexPage as IP
import qualified Rules.Blog as Blog
import qualified Rules.Media as Media
import qualified Rules.Src.JavaScript as Js
import qualified Rules.Src.Style as Style
import qualified Rules.TopPage as TopPage
import qualified Rules.Vendor as Vendor
import qualified Vendor.FontAwesome as FA

Expand Down Expand Up @@ -145,10 +144,10 @@ versionOption = OA.infoOption vopt $ mconcat [OA.long "version", OA.help "Show v
optsParser :: OA.ParserInfo Opts
optsParser = OA.info (OA.helper <*> versionOption <*> programOptions) $ mconcat [
OA.fullDesc
, OA.progDesc $ concat [
"The static site roki.dev compiler version "
, OA.progDesc $ unwords [
"The static site roki.dev compiler version"
, showVersion P.version
, " powerted by Hakyll"
, "powerted by Hakyll"
]
]

Expand All @@ -157,14 +156,18 @@ techBlogConf = B.BlogConfig {
B.blogName = TB.blogName
, B.blogDescription = TB.blogDesc
, B.blogFont = RokiLog.font
, B.blogPageEntriesNum = 5
, B.blogPrevNextTitleMaxNum = 6
, B.blogFeedRecentNum = 20
, B.blogIsPreview = False
, B.blogHeaderAdditional = mempty
, B.blogBeforeContentBodyAdditional = TL.unpack $ renderText RokiLog.gAdSenseBeforeContentBody
, B.blogFooterAdditional = TL.unpack $ renderText RokiLog.footerAdditionalComponent
, B.blogBeforeContentBodyAdditional = RokiLog.gAdSenseBeforeContentBody
, B.blogFooterAdditional = RokiLog.footerAdditionalComponent
, B.blogTagBuilder = TB.buildTags
, B.blogTagPagesPath = TB.tagPagesPath
, B.blogEntryPattern = TB.entryPattern
, B.blogEntryFilesPattern = TB.entryFilesPattern
, B.blogAtomConfig = TB.atomConfig
, B.blogFeedConfig = TB.feedConfig
, B.blogContentSnapshot = TB.contentSnapshot
, B.blogYearlyArchivesBuilder = TB.buildYearlyArchives
, B.blogMonthlyArchivesBuilder = TB.buildMonthlyArchives
Expand All @@ -179,14 +182,18 @@ diaryConf = B.BlogConfig {
B.blogName = AB.blogName
, B.blogDescription = AB.blogDesc
, B.blogFont = RokiDiary.font
, B.blogHeaderAdditional = TL.unpack $ renderText RokiDiary.gAdSenseHeader
, B.blogBeforeContentBodyAdditional = TL.unpack $ renderText RokiDiary.gAdSenseBeforeContentBody
, B.blogFooterAdditional = TL.unpack $ renderText RokiDiary.gAdSenseFooter
, B.blogPageEntriesNum = 5
, B.blogPrevNextTitleMaxNum = 6
, B.blogFeedRecentNum = 20
, B.blogIsPreview = False
, B.blogHeaderAdditional = RokiDiary.gAdSenseHeader
, B.blogBeforeContentBodyAdditional = RokiDiary.gAdSenseBeforeContentBody
, B.blogFooterAdditional = RokiDiary.gAdSenseFooter
, B.blogTagBuilder = AB.buildTags
, B.blogTagPagesPath = AB.tagPagesPath
, B.blogEntryPattern = AB.entryPattern
, B.blogEntryFilesPattern = AB.entryFilesPattern
, B.blogAtomConfig = AB.atomConfig
, B.blogFeedConfig = AB.feedConfig
, B.blogContentSnapshot = AB.contentSnapshot
, B.blogYearlyArchivesBuilder = AB.buildYearlyArchives
, B.blogMonthlyArchivesBuilder = AB.buildMonthlyArchives
Expand All @@ -205,8 +212,14 @@ main = do
}
writer = if optPreviewFlag opts then writerPreviewOptions else writerOptions
blogConfs = [
techBlogConf { B.blogWriterOptions = writer }
, diaryConf { B.blogWriterOptions = writer }
techBlogConf {
B.blogIsPreview = optPreviewFlag opts
, B.blogWriterOptions = writer
}
, diaryConf {
B.blogIsPreview = optPreviewFlag opts
, B.blogWriterOptions = writer
}
]

hakyllWithArgs conf (Options (optVerbose opts) $ mapIL (optInternalLinks opts) $ optCmd opts $ conf) $ do
Expand All @@ -215,10 +228,12 @@ main = do
*> Style.rules
*> Js.rules
faIcons <- fold <$> preprocess FA.loadFontAwesome
mapM_ (flip (B.blogRules (optPreviewFlag opts)) faIcons) blogConfs
IP.rules blogConfs faIcons
mapM_ (runReaderT $ Blog.rules faIcons) blogConfs
TopPage.rules blogConfs faIcons

match (fromString $ intercalateDir ["contents", "templates", "**"]) $
match "CNAME" $ route idRoute >> compile copyFileCompiler
match "ads.txt" $ route idRoute >> compile copyFileCompiler
match (fromString $ joinPath ["contents", "templates", "**"]) $
compile templateBodyCompiler
where
mapIL b (Check _) = Check b
Expand Down
32 changes: 16 additions & 16 deletions package-lock.json

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion package.json
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,6 @@
},
"dependencies": {
"d3": "^7.8.5",
"mathjs": "^11.10.0"
"mathjs": "^11.11.0"
}
}
25 changes: 22 additions & 3 deletions roki-web.cabal
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
cabal-version: 1.12

-- This file has been generated from package.yaml by hpack version 0.34.4.
-- This file has been generated from package.yaml by hpack version 0.35.1.
--
-- see: https://github.com/sol/hpack
--
-- hash: 66bb1c61d4e036f477dc3dada73818a451a46c8c1f28b6b91563835fc2671ddb
-- hash: 2770a89839ea340a18ab2d819e48d1c9b1dca82adca5edba282a46800f69d7cb

name: roki-web
version: 1.0.0.0
Expand Down Expand Up @@ -36,7 +36,9 @@ library
Config.Program
Config.RegexUtils
Config.Site
Config.TopPage
Contexts
Contexts.Blog
Contexts.Core
Contexts.Field
Contexts.Field.RokiDiary
Expand All @@ -51,10 +53,27 @@ library
Media.SVG
Rules.Blog
Rules.Blog.Core
Rules.IndexPage
Rules.Blog.EachPosts
Rules.Blog.EachPosts.Utils
Rules.Blog.EachPostSeries
Rules.Blog.Feed.Atom
Rules.Blog.Feed.RSS
Rules.Blog.Feed.Utils
Rules.Blog.Footer
Rules.Blog.Index
Rules.Blog.ListPage
Rules.Blog.Paginate.MonthlyPosts
Rules.Blog.Paginate.TaggedPosts
Rules.Blog.Paginate.Utils
Rules.Blog.Paginate.YearlyPosts
Rules.Blog.Search
Rules.Blog.Sitemap
Rules.Blog.Type
Rules.Blog.Utils
Rules.Media
Rules.Src.JavaScript
Rules.Src.Style
Rules.TopPage
Rules.Vendor
Utils
Vendor.FontAwesome
Expand Down
2 changes: 2 additions & 0 deletions src/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,10 @@ module Config (
module Config.Site
, module Config.Program
, module Config.Contributions
, module Config.Blog
) where

import Config.Blog
import Config.Contributions
import Config.Program
import Config.Site
14 changes: 9 additions & 5 deletions src/Config/Blog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,17 +11,21 @@ import Lucid.Base (Html)
import Text.Pandoc.Options (WriterOptions)

data BlogConfig m = BlogConfig {
blogName :: String
blogIsPreview :: Bool
, blogName :: String
, blogDescription :: String
, blogFont :: Html ()
, blogHeaderAdditional :: String
, blogBeforeContentBodyAdditional :: String
, blogFooterAdditional :: String
, blogPageEntriesNum :: Int
, blogPrevNextTitleMaxNum :: Int
, blogFeedRecentNum :: Int
, blogHeaderAdditional :: Html ()
, blogBeforeContentBodyAdditional :: Html ()
, blogFooterAdditional :: Html ()
, blogTagBuilder :: m Tags
, blogTagPagesPath :: FilePath -> FilePath
, blogEntryPattern :: Pattern
, blogEntryFilesPattern :: Pattern
, blogAtomConfig :: FeedConfiguration
, blogFeedConfig :: FeedConfiguration
, blogContentSnapshot :: String
, blogYearlyArchivesBuilder :: m YearlyArchives
, blogMonthlyArchivesBuilder :: m MonthlyArchives
Expand Down
7 changes: 3 additions & 4 deletions src/Config/Blogs/AnotherBlog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Config.Blogs.AnotherBlog (
, blogDesc
, entryPattern
, entryFilesPattern
, atomConfig
, feedConfig
, contentSnapshot
, tagPagesPath
, buildTags
Expand Down Expand Up @@ -44,8 +44,8 @@ entryPattern = BU.entryPattern blogName
entryFilesPattern :: H.Pattern
entryFilesPattern = BU.entryFilesPattern blogName

atomConfig :: FeedConfiguration
atomConfig = FeedConfiguration {
feedConfig :: FeedConfiguration
feedConfig = FeedConfiguration {
feedTitle = blogName
, feedWebRoot = "https://" <> siteName
, feedBlogName = blogName
Expand Down Expand Up @@ -78,4 +78,3 @@ monthlyPagePath = BU.monthlyPagePath blogName
buildMonthlyArchives :: (H.MonadMetadata m, MonadFail m) => m A.MonthlyArchives
buildMonthlyArchives = BU.buildMonthlyArchives blogName


11 changes: 6 additions & 5 deletions src/Config/Blogs/TechBlog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Config.Blogs.TechBlog (
, blogDesc
, entryPattern
, entryFilesPattern
, atomConfig
, feedConfig
, contentSnapshot
, tagPagesPath
, buildTags
Expand Down Expand Up @@ -33,9 +33,10 @@ blogName = "roki.log"
blogDesc :: String
blogDesc = TL.unpack $ renderText $ do
a_ [href_ $ T.pack $ "/" <> blogName] $ fromString blogName
p_ [class_ "is-inline"] $
p_ [class_ "is-inline"] $ mconcat [
" is a blog written about efforts and learning related to technology, mathematics, "
<> "etc (Most of the content of the article is written in Japanese)."
, "etc (Most of the content of the article is written in Japanese)."
]

-- contents/roki.log/year/month/day/title/index.md
entryPattern :: H.Pattern
Expand All @@ -44,8 +45,8 @@ entryPattern = BU.entryPattern blogName
entryFilesPattern :: H.Pattern
entryFilesPattern = BU.entryFilesPattern blogName

atomConfig :: FeedConfiguration
atomConfig = FeedConfiguration {
feedConfig :: FeedConfiguration
feedConfig = FeedConfiguration {
feedTitle = blogName
, feedWebRoot = "https://" <> siteName
, feedBlogName = blogName
Expand Down
Loading

0 comments on commit bdaae33

Please sign in to comment.