nani.wtf/ssg/src/Main.hs

282 lines
7.0 KiB
Haskell
Raw Normal View History

2020-09-22 04:03:52 +02:00
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad (forM_)
import Data.Maybe (fromMaybe)
import Hakyll
import Text.Pandoc
( Extension (Ext_fenced_code_attributes, Ext_footnotes, Ext_gfm_auto_identifiers, Ext_implicit_header_references, Ext_smart),
2020-09-22 04:03:52 +02:00
Extensions,
2022-03-28 03:13:58 +02:00
Pandoc,
2020-09-22 04:03:52 +02:00
ReaderOptions,
2021-06-13 06:02:29 +02:00
WriterOptions (writerHighlightStyle),
2020-09-22 04:03:52 +02:00
extensionsFromList,
githubMarkdownExtensions,
readerExtensions,
writerExtensions,
)
2021-06-13 06:02:29 +02:00
import Text.Pandoc.Highlighting (Style, breezeDark, styleToCss)
import Debug.Trace
import Data.Map (mapKeys)
2022-03-28 03:13:58 +02:00
import Text.Pandoc.Walk ( walk, walkM )
2020-09-22 04:03:52 +02:00
2022-03-19 00:59:36 +01:00
-- ---------
import Formats.Gogen
import Formats.Posts
import Util.Hakyll.Routes
import Util.Hakyll.Context
import Util.Hash
2022-03-28 03:13:58 +02:00
import Preprocessing.LogoLinks
import Preprocessing.Graphviz
2022-03-19 00:59:36 +01:00
2021-08-03 02:01:55 +02:00
--------------------------------------------------------------------------------
2020-09-22 04:03:52 +02:00
-- CONFIG
root :: String
root =
2022-03-13 22:34:31 +01:00
"https://www.nani.wtf/test/"
2020-09-22 04:03:52 +02:00
siteName :: String
siteName =
2022-03-13 22:34:31 +01:00
"Nani~"
2020-09-22 04:03:52 +02:00
config :: Configuration
config =
defaultConfiguration
2021-08-03 02:01:55 +02:00
{ destinationDirectory = "dist"
, ignoreFile = const False
, previewHost = "127.0.0.1"
, previewPort = 8000
, providerDirectory = "src"
, storeDirectory = "ssg/_cache"
, tmpDirectory = "ssg/_tmp"
2020-09-22 04:03:52 +02:00
}
2021-08-03 02:01:55 +02:00
--------------------------------------------------------------------------------
2020-09-22 04:03:52 +02:00
-- BUILD
main :: IO ()
main = hakyllWith config $ do
fileHashes <- preprocess (mapKeys (fromFilePath . drop 4 . toFilePath) <$> mkFileHashes "src/posts")
2020-09-22 04:03:52 +02:00
forM_
2021-08-03 02:01:55 +02:00
[ "CNAME"
, "favicon.ico"
, "_config.yml"
2022-03-27 04:00:05 +02:00
, "images/**"
2021-08-03 02:01:55 +02:00
, "js/*"
, "fonts/*"
2020-09-22 04:03:52 +02:00
]
$ \f -> match f $ do
route idRoute
compile copyFileCompiler
2021-06-13 06:02:29 +02:00
2022-03-13 22:34:31 +01:00
match "robots.txt" $ do
route (constRoute "public/robots.txt")
compile copyFileCompiler
2020-09-22 04:03:52 +02:00
match "css/*" $ do
route idRoute
compile compressCssCompiler
2021-06-13 06:02:29 +02:00
2020-09-22 04:03:52 +02:00
match "posts/*" $ do
let ctx = constField "type" "article" <> postCtx
2021-06-13 06:02:29 +02:00
route $ postRoute fileHashes
2020-09-22 04:03:52 +02:00
compile $
2022-03-27 04:22:59 +02:00
getResourceBody
>>= replaceLogoLinks
>>= pandocRendererCustom
>>= loadAndApplyTemplate "templates/post.html" ctx
>>= saveSnapshot "content"
>>= loadAndApplyTemplate "templates/default.html" ctx
2021-06-13 06:02:29 +02:00
match "gogen/*" $ do
2022-03-19 00:59:36 +01:00
let ctx =
constField "type" "article"
2022-03-23 13:46:07 +01:00
<> constField "root" root
<> constField "siteName" siteName
<> gogenCtx
2022-03-19 00:59:36 +01:00
route $ setExtension ".html"
compile $ do
pandocCompilerCustom
>>= loadAndApplyTemplate "templates/gogen.html" ctx
2022-03-19 00:59:36 +01:00
>>= saveSnapshot "content"
>>= loadAndApplyTemplate "templates/default.html" ctx
2022-03-27 04:22:59 +02:00
match "*debug.md" $ do
let ctx = constField "type" "article" <> postCtx
route $ constRoute "debug.html"
compile $
getResourceBody
>>= replaceLogoLinks
>>= pandocRendererCustom
>>= loadAndApplyTemplate "templates/post.html" ctx
>>= saveSnapshot "content"
>>= loadAndApplyTemplate "templates/default.html" ctx
2022-03-19 00:59:36 +01:00
2020-09-22 04:03:52 +02:00
match "index.html" $ do
route idRoute
compile $ do
2022-03-19 00:59:36 +01:00
-- posts :: Compiler
2020-09-22 04:03:52 +02:00
posts <- recentFirst =<< loadAll "posts/*"
gogen <- loadAll "gogen/*"
2021-06-13 06:02:29 +02:00
2020-09-22 04:03:52 +02:00
let indexCtx =
2022-03-19 00:59:36 +01:00
listField "posts" postCtx (return posts)
<> listField "gogen" gogenCtx (return gogen)
2020-09-22 04:03:52 +02:00
<> constField "root" root
<> constField "siteName" siteName
<> defaultContext
2021-06-13 06:02:29 +02:00
2020-09-22 04:03:52 +02:00
getResourceBody
>>= applyAsTemplate indexCtx
>>= loadAndApplyTemplate "templates/default.html" indexCtx
2021-06-13 06:02:29 +02:00
match "templates/*" $
compile templateBodyCompiler
2021-06-13 06:02:29 +02:00
2022-03-13 22:34:31 +01:00
create ["public/sitemap.xml"] $ do
2020-09-22 04:03:52 +02:00
route idRoute
compile $ do
posts <- recentFirst =<< loadAll "posts/*"
2021-06-13 06:02:29 +02:00
let pages = posts
2020-09-22 04:03:52 +02:00
sitemapCtx =
constField "root" root
<> constField "siteName" siteName
<> listField "pages" postCtx (return pages)
2021-06-13 06:02:29 +02:00
2020-09-22 04:03:52 +02:00
makeItem ("" :: String)
>>= loadAndApplyTemplate "templates/sitemap.xml" sitemapCtx
2021-06-13 06:02:29 +02:00
2022-03-13 22:34:31 +01:00
create ["public/rss.xml"] $ do
2020-09-22 04:03:52 +02:00
route idRoute
compile (feedCompiler renderRss)
2021-06-13 06:02:29 +02:00
2022-03-13 22:34:31 +01:00
create ["public/atom.xml"] $ do
2020-09-22 04:03:52 +02:00
route idRoute
compile (feedCompiler renderAtom)
2021-06-13 06:02:29 +02:00
create ["css/code.css"] $ do
route idRoute
compile (makeStyle pandocHighlightStyle)
2021-08-03 02:01:55 +02:00
--------------------------------------------------------------------------------
2021-06-13 06:02:29 +02:00
-- COMPILER HELPERS
makeStyle :: Style -> Compiler (Item String)
makeStyle =
makeItem . compressCss . styleToCss
2021-08-03 02:01:55 +02:00
--------------------------------------------------------------------------------
2020-09-22 04:03:52 +02:00
-- CONTEXT
feedCtx :: Context String
feedCtx =
titleCtx
<> postCtx
<> bodyField "description"
postCtx :: Context String
postCtx =
constField "root" root
<> defaultConstField "lang" "en"
<> constField "author" "h7x4"
2020-09-22 04:03:52 +02:00
<> constField "siteName" siteName
<> dateField "date" "%Y-%m-%d"
<> defaultContext
titleCtx :: Context String
titleCtx =
field "title" updatedTitle
2021-08-03 02:01:55 +02:00
--------------------------------------------------------------------------------
2020-09-22 04:03:52 +02:00
-- TITLE HELPERS
replaceAmp :: String -> String
replaceAmp =
replaceAll "&" (const "&amp;")
replaceTitleAmp :: Metadata -> String
replaceTitleAmp =
replaceAmp . safeTitle
safeTitle :: Metadata -> String
safeTitle =
fromMaybe "no title" . lookupString "title"
updatedTitle :: Item a -> Compiler String
updatedTitle =
fmap replaceTitleAmp . getMetadata . itemIdentifier
2021-08-03 02:01:55 +02:00
--------------------------------------------------------------------------------
2020-09-22 04:03:52 +02:00
-- PANDOC
pandocCompilerCustom :: Compiler (Item String)
pandocCompilerCustom =
pandocCompilerWith pandocReaderOpts pandocWriterOpts
2022-03-27 04:00:05 +02:00
pandocRendererCustom :: Item String -> Compiler (Item String)
pandocRendererCustom =
2022-03-28 03:13:58 +02:00
renderPandocWithTransformM pandocReaderOpts pandocWriterOpts transform
where
transform :: Pandoc -> Compiler Pandoc
transform = unsafeCompiler . walkM codeBlock
2022-03-27 04:00:05 +02:00
2020-09-22 04:03:52 +02:00
pandocExtensionsCustom :: Extensions
pandocExtensionsCustom =
githubMarkdownExtensions
<> extensionsFromList
2021-08-03 02:01:55 +02:00
[ Ext_fenced_code_attributes
, Ext_gfm_auto_identifiers
, Ext_implicit_header_references
, Ext_smart
, Ext_footnotes
2020-09-22 04:03:52 +02:00
]
pandocReaderOpts :: ReaderOptions
pandocReaderOpts =
defaultHakyllReaderOptions
{ readerExtensions = pandocExtensionsCustom
}
pandocWriterOpts :: WriterOptions
pandocWriterOpts =
defaultHakyllWriterOptions
{ writerExtensions = pandocExtensionsCustom
2021-06-13 06:02:29 +02:00
, writerHighlightStyle = Just pandocHighlightStyle
2020-09-22 04:03:52 +02:00
}
2021-06-13 06:02:29 +02:00
pandocHighlightStyle :: Style
pandocHighlightStyle =
breezeDark -- https://hackage.haskell.org/package/pandoc/docs/Text-Pandoc-Highlighting.html
2020-09-22 04:03:52 +02:00
-- FEEDS
type FeedRenderer =
FeedConfiguration ->
Context String ->
[Item String] ->
Compiler (Item String)
feedCompiler :: FeedRenderer -> Compiler (Item String)
feedCompiler renderer =
renderer feedConfiguration feedCtx
=<< recentFirst
=<< loadAllSnapshots "posts/*" "content"
feedConfiguration :: FeedConfiguration
feedConfiguration =
FeedConfiguration
2022-03-13 22:34:31 +01:00
{ feedTitle = "www.nani.wtf"
, feedDescription = "???"
, feedAuthorName = "h7x4"
, feedAuthorEmail = "h7x4@protonmail.com"
2021-08-03 02:01:55 +02:00
, feedRoot = root
}