This commit is contained in:
Yann Esposito (Yogsototh) 2021-04-27 19:24:58 +02:00
parent 14361d5289
commit 8944a17762
Signed by untrusted user who does not match committer: yogsototh
GPG Key ID: 7B19A4C650D59646
20 changed files with 5 additions and 826 deletions

View File

@ -1,5 +0,0 @@
# Revision history for her-esy-fun
## 0.1.0.0 -- YYYY-mm-dd
* First version. Released on an unsuspecting world.

View File

@ -1 +0,0 @@
app/Shakefile.hs

View File

@ -1,6 +0,0 @@
#+TITLE: Project TODO
* DONE Display size of current page (text + images)
CLOSED: [2020-02-23 Sun 00:18]
* TODO Delete classes not present in both CSS and HTML

View File

@ -1,502 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
import Protolude
import Development.Shake
import Development.Shake.FilePath
import Data.Time.Format.ISO8601 (iso8601Show)
import qualified Data.Time.Clock as Clock
import Control.Monad.Fail
import Data.Aeson
import Data.Default ( Default(def) )
import qualified Data.Text as T
import Text.Mustache
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as Pandoc
import Text.Pandoc.Definition ( Pandoc(..)
, Block(..)
, Inline(..)
, MetaValue(..)
, nullMeta
, docTitle
, docDate
, docAuthors
, lookupMeta
)
import Text.Pandoc.Options ( ReaderOptions(..)
, WriterOptions(..)
, ObfuscationMethod(..)
, HTMLMathMethod(..)
)
import qualified Text.Pandoc.Readers as Readers
import Text.Pandoc.Walk (Walkable(..))
import qualified Text.Pandoc.Writers as Writers
import qualified Text.Pandoc.Templates as Templates
main :: IO ()
main = shakeArgs shOpts buildRules
where
shOpts =
shakeOptions
{ shakeVerbosity = Chatty
, shakeLintInside = ["\\"]
}
-- Configuration
-- Should probably go in a Reader Monad
srcDir :: FilePath
srcDir = "src"
siteDir :: FilePath
siteDir = "_site"
optimDir :: FilePath
optimDir = "_optim"
-- BlogPost data structure (a bit of duplication because the metas are in Pandoc)
data BlogPost =
BlogPost { postTitle :: T.Text
, postDate :: T.Text
, postAuthor :: T.Text
, postUrl :: FilePath
, postSrc :: FilePath
, postTags :: [T.Text]
, postDescr :: T.Text
, postToc :: Bool
, postBody :: Pandoc
}
inlineToText :: PandocMonad m => [Inline] -> m T.Text
inlineToText inline =
Writers.writeAsciiDoc def (Pandoc nullMeta [Plain inline])
reformatDate :: Text -> Text
reformatDate = T.takeWhile (/= ' ') . (T.dropAround dateEnvelope)
where
dateEnvelope ' ' = True
dateEnvelope '\n' = True
dateEnvelope '\t' = True
dateEnvelope '[' = True
dateEnvelope ']' = True
dateEnvelope _ = False
getBlogpostFromMetas
:: (MonadIO m, MonadFail m) => [Char] -> Bool -> Pandoc -> m BlogPost
getBlogpostFromMetas path toc pandoc@(Pandoc meta _) = do
eitherBlogpost <- liftIO $ Pandoc.runIO $ do
title <- fmap (T.dropEnd 1) $ inlineToText $ docTitle meta
date <- fmap reformatDate $ inlineToText $ docDate meta
author <- case head $ docAuthors meta of
Just m -> fmap T.strip $ inlineToText m
Nothing -> return ""
let tags = tagsToList $ lookupMeta "keywords" meta
description = descr $ lookupMeta "description" meta
url = "/" </> dropDirectory1 path -<.> "org"
return $ BlogPost title date author url path tags description toc pandoc
case eitherBlogpost of
Left _ -> fail "BAD"
Right bp -> return bp
where
tagsToList (Just (MetaList ms)) = map toStr ms
tagsToList _ = []
descr (Just (MetaString t)) = t
descr _ = ""
toStr (MetaString t) = t
toStr (MetaInlines inlines) = T.intercalate " " $ map inlineToTxt inlines
toStr _ = ""
inlineToTxt (Str t) = t
inlineToTxt _ = ""
sortByPostDate :: [BlogPost] -> [BlogPost]
sortByPostDate =
sortBy (\a b-> compare (postDate b) (postDate a))
build :: FilePath -> FilePath
build = (</>) siteDir
genAllDeps :: [FilePattern] -> Action [FilePath]
genAllDeps patterns = do
allMatchedFiles <- getDirectoryFiles srcDir patterns
allMatchedFiles &
filter ((/= "html") . takeExtension) &
filter (null . takeExtension) &
map (siteDir </>) &
return
buildRules :: Rules ()
buildRules = do
cleanRule
fastRule
allRule
fullRule
getPost <- mkGetPost
getPosts <- mkGetPosts getPost
getTemplate <- mkGetTemplate
build "**" %> \out -> do
let asset = dropDirectory1 out
case (takeExtension asset) of
".html" -> do
if out == siteDir </> "index.html"
then buildArchive getPosts getTemplate out
else do
htmlExists <- doesFileExist (srcDir </> asset)
if htmlExists
then copyFileChanged (srcDir </> asset) out
else genHtmlAction getPost getTemplate out
".pdf" -> do
txtExists <- doesFileExist (srcDir </> asset)
if txtExists
then copyFileChanged (srcDir </> asset) out
else genPdfAction getPost out
".gmi" -> do
fileExists <- doesFileExist (srcDir </> asset)
if fileExists
then copyFileChanged (srcDir </> asset) out
else if out == siteDir </> "index.gmi"
then buildGeminiArchive getPosts out
else genGeminiAction out
".jpg" -> compressImage asset
".jpeg" -> compressImage asset
".gif" -> compressImage asset
".png" -> compressImage asset
_ -> copyFileChanged (srcDir </> asset) out
optimDir </> "rss.xml" %> \_ -> do
needAll
command_[] "engine/pre-deploy.sh" []
welcomeTxt :: Text
welcomeTxt = toS $ T.intercalate "\n" $
[ "Welcome to my small place on the Internet."
]
buildArchive
:: (() -> Action [BlogPost])
-> (FilePath -> Action Template) -> [Char] -> Action ()
buildArchive getPosts getTemplate out = do
css <- genAllDeps ["//*.css"]
posts <- fmap sortByPostDate $ getPosts ()
need $ css <> map postSrc posts
let
title :: Text
title = "#+title: Yann Esposito's blog"
menu = "@@html:<a href=\"/index.html\">Home</a> | <a href=\"/slides.html\">Slides</a> | <a href=\"/about-me.html\">About</a>@@"
articleList = toS $ T.intercalate "\n" $ map postInfo posts
olderArchives = "---\n\n@@html:<a href=\"/Scratch/en/blog/index.html\">Older Archives from my previous blog</a>@@"
fileContent = title <> "\n\n" <> menu <> "\n\n" <> welcomeTxt <> "\n\n" <> articleList <> olderArchives
eitherResult <- liftIO $ Pandoc.runIO $ Readers.readOrg (def { readerStandalone = True }) (toS fileContent)
bp <- case eitherResult of
Left _ -> fail "BAD"
Right pandoc -> getBlogpostFromMetas out False pandoc
innerHtml <- genHtml bp
template <- getTemplate ("templates" </> "main.mustache")
let htmlContent =
renderMustache template
$ object [ "title" .= postTitle bp
, "author" .= postAuthor bp
, "date" .= postDate bp
, "tags" .= postTags bp
, "description" .= postDescr bp
, "body" .= innerHtml
]
writeFile' out (toS htmlContent)
geminiMenu :: Text
geminiMenu = T.intercalate "\n"
[ "=> /index.gmi Home"
, "=> /gem-atom.xml Feed"
, "=> /slides.gmi Slides"
, "=> /about-me.gmi About me"
]
buildGeminiArchive
:: (() -> Action [BlogPost])
-> [Char] -> Action ()
buildGeminiArchive getPosts out = do
posts <- fmap sortByPostDate $ getPosts ()
need $ map postSrc posts
let
title :: Text
title = "# Yann Esposito's posts"
articleList = toS $ T.intercalate "\n" $ map postGeminiInfo posts
fileContent = title
<> "\n\n" <> welcomeTxt
<> "\n\n" <> geminiMenu
<> "\n\n" <> "## Articles"
<> "\n\n" <> articleList
writeFile' out (toS fileContent)
postGeminiInfo :: BlogPost -> Text
postGeminiInfo bp =
"=> " <> (toS (postUrl bp -<.> ".gmi")) <> " " <> date <> ": " <> (postTitle bp)
where
date = T.takeWhile (/= ' ') (postDate bp)
postInfo :: BlogPost -> Text
postInfo bp =
"| " <> date <> " | " <> orglink <> " |"
where
date = T.takeWhile (/= ' ') (postDate bp)
orglink = "[[file:" <> (toS (postUrl bp)) <> "][" <> (postTitle bp) <> "]]"
replaceLinks :: Pandoc -> Pandoc
replaceLinks = walk replaceOrgLink
where
replaceOrgLink :: Inline -> Inline
replaceOrgLink lnk@(Link attr inl (url,txt)) =
if takeExtension (toS url) == ".org"
then Link attr inl ((toS (toS url -<.> ".html")),txt)
else lnk
replaceOrgLink x = x
orgContentToText :: (MonadIO m, MonadFail m) => Text -> m Text
orgContentToText org = do
eitherResult <- liftIO $ Pandoc.runIO $ Readers.readOrg (def { readerStandalone = True }) org
pandoc <- case eitherResult of
Left _ -> fail "BAD"
Right p -> return p
eitherHtml <- liftIO $ Pandoc.runIO $
Writers.writeHtml5String (def {writerEmailObfuscation = ReferenceObfuscation}) pandoc
case eitherHtml of
Left _ -> fail "BAD"
Right innerHtml -> return innerHtml
postamble :: (MonadIO m, MonadFail m) => Text -> BlogPost -> m Text
postamble now bp =
orgContentToText $ unlines $
[ "@@html:<footer>@@"
, "@@html:<i>Any comment? Click on my email below and I'll add it.</i>@@"
, ""
, "| author | @@html:<span class=\"author\">@@ [[mailto:Yann Esposito <yann@esposito.host>?subject=yblog: " <> (postTitle bp) <> "][Yann Esposito <yann@esposito.host>]] @@html:</span>@@ |"
, "| gpg | [[file:files/publickey.txt][CB420F8005F1A662]] |"
, "| tags | " <> T.intercalate " " (map ("#"<>) (postTags bp)) <> " |"
, "| date | " <> postDate bp <> " |"
, "| rss | [[file:/rss.xml][RSS]] ([[https://validator.w3.org/feed/check.cgi?url=https%3A%2F%2Fher.esy.fun%2Frss.xml][validate]]) |"
, "| size | @@html:<span class=\"web-file-size\">XXK (html XXK, css XXK, img XXK)</span>@@ |"
, "| gz | @@html:<span class=\"gzweb-file-size\">XXK (html XXK, css XXK, img XXK)</span>@@ |"
, "| generated | " <> now <> " |"
, ""
, "@@html:</footer>@@"
]
tpltxt :: Text
tpltxt = T.unlines [
"$if(toc)$"
, "<nav id=\"$idprefix$TOC\" role=\"doc-toc\">"
, "$if(toc-title)$"
, "<h2 id=\"$idprefix$toc-title\">$toc-title$</h2>"
, "$endif$"
, "$table-of-contents$"
, "</nav>"
, "$endif$"
, "$body$"
]
getPostTpl :: IO (Templates.Template Text)
getPostTpl = do
etpl <- Templates.compileTemplate "blog.template" tpltxt
case etpl of
Left e -> fail e
Right tpl -> return tpl
genHtml :: (MonadIO m, MonadFail m) => BlogPost -> m Text
genHtml bp = do
let htmlBody = replaceLinks (postBody bp)
eitherHtml <- liftIO $ do
tpl <- getPostTpl
Pandoc.runIO $ do
Writers.writeHtml5String
(def { writerTableOfContents = postToc bp
, writerTemplate = Just tpl
, writerTOCDepth = 3
, writerEmailObfuscation = ReferenceObfuscation
, writerHTMLMathMethod = MathML
})
htmlBody
body <- case eitherHtml of
Left _ -> fail "BAD"
Right innerHtml -> return innerHtml
now <- liftIO Clock.getCurrentTime
footer <- postamble (toS (iso8601Show now)) bp
return (body <> footer)
origin :: Text
origin = "https://her.esy.fun"
geminiOrigin :: Text
geminiOrigin = "gemini://her.esy.fun"
genHtmlAction
:: (FilePath -> Action BlogPost)
-> (FilePath -> Action Template) -> [Char] -> Action ()
genHtmlAction getPost getTemplate out = do
let tplname = case takeDirectory1 (dropDirectory1 out) of
"posts" -> "post.mustache"
"slides" -> "slide.mustache"
"drafts" -> "post.mustache"
_ -> "main.mustache"
let templateFile = "templates" </> tplname
template <- getTemplate templateFile
let srcFile = srcDir </> (dropDirectory1 (out -<.> "org"))
liftIO $ putText $ "need: " <> (toS srcFile) <> " -> " <> (toS out)
need [srcFile,templateFile,"templates" </> "menu.mustache","Shakefile.hs"]
bp <- getPost srcFile
innerHtml <- genHtml bp
let htmlContent =
renderMustache template
$ object [ "title" .= postTitle bp
, "author" .= postAuthor bp
, "date" .= postDate bp
, "tags" .= postTags bp
, "description" .= postDescr bp
, "body" .= innerHtml
, "orgsource" .= T.pack (postUrl bp -<.> "org")
, "txtsource" .= T.pack (postUrl bp -<.> "gmi")
, "geminiurl" .= T.pack (toS geminiOrigin <> postUrl bp -<.> "gmi")
, "pdf" .= T.pack (postUrl bp -<.> "pdf")
, "permalink" .= T.pack (toS origin <> postUrl bp -<.> "html")
]
writeFile' out (toS htmlContent)
genPdfAction :: p -> [Char] -> Action ()
genPdfAction _getPost out = do
let srcFile = srcDir </> (dropDirectory1 (out -<.> "org"))
need [srcFile,"Shakefile.hs"]
command_ [] "pandoc"
["--pdf-engine=xelatex"
, "--resource-path=" <> takeDirectory srcFile
, srcFile
, "-H", "engine" </> "deeplist.tex"
, "-V", "mainfont:CMU Serif"
, "-V", "mainfontoptions:Renderer=OpenType, Mapping=tex-text, ItalicFeatures={Alternate = 0}, Ligatures={Common,Rare,Historic,Contextual},Contextuals=Inner,Alternate=1"
, "-V", "monofont:Menlo"
, "-V", "monofontoptions:Scale=0.7"
, "-o", out ]
-- genGemini :: (MonadIO m, MonadFail m) => BlogPost -> m Text
-- genGemini bp = do
-- eitherMd <- liftIO $ Pandoc.runIO $ Writers.writeMarkdown def (postBody bp)
-- case eitherMd of
-- Left _ -> fail "BAD"
-- Right innerMd -> return innerMd
genGeminiAction :: [Char] -> Action ()
genGeminiAction out = do
let srcFile = srcDir </> (dropDirectory1 (out -<.> "org"))
need [srcFile]
command_ [] "./engine/org2gemini.sh" [ srcFile, out ]
allHtmlAction :: Action ()
allHtmlAction = do
allOrgFiles <- getDirectoryFiles srcDir ["//*.org"]
let allHtmlFiles = map (-<.> "html") allOrgFiles
need (map build allHtmlFiles)
allPdfAction :: Action ()
allPdfAction = do
allOrgFiles <- getDirectoryFiles srcDir ["//*.org"]
let allHtmlFiles = map (-<.> "pdf") allOrgFiles
need (map build allHtmlFiles)
allGeminiAction :: Action ()
allGeminiAction = do
allOrgFiles <- getDirectoryFiles srcDir ["//*.org"]
let allGeminiFiles = map (-<.> "gmi") allOrgFiles
need (map build $ allGeminiFiles <> ["index.gmi"])
compressImage :: FilePath -> Action ()
compressImage img = do
let src = srcDir </> img
dst = siteDir </> img
need [src]
let dir = takeDirectory dst
dirExists <- doesDirectoryExist dir
when (not dirExists) $
command [] "mkdir" ["-p", dir]
command_ [] "convert" [ src
, "-strip"
, "-resize","960x960>"
, "-interlace","Plane"
, "-quality","85"
, "-define","filter:blur=0.75"
, "-filter","Gaussian"
-- , "-ordered-dither","o4x4,4"
, dst ]
needFast :: Action ()
needFast = do
allAssets <- filter (/= ".DS_Store") <$> getDirectoryFiles srcDir ["**"]
need (map build $ allAssets <> ["index.html"])
allHtmlAction
allGeminiAction
fastRule :: Rules ()
fastRule =
withTargetDocs "generate html" $
phony "fast" $
needFast
needAll :: Action ()
needAll = do
needFast
allPdfAction
allGeminiAction
allRule :: Rules ()
allRule =
withTargetDocs "generate all, no optim" $
phony "all" $
needAll
fullRule :: Rules ()
fullRule =
withTargetDocs "generate all and optim" $
phony "full" $
need [optimDir </> "rss.xml"]
cleanRule :: Rules ()
cleanRule =
phony "clean" $ do
putInfo "Cleaning files in _site and _optim"
forM_ [siteDir,optimDir] $ flip removeFilesAfter ["**"]
mkGetTemplate :: Rules (FilePath -> Action Template)
mkGetTemplate = newCache $ \path -> do
fileContent <- readFile' path
header <- readFile' ("templates" </> "header.mustache")
menu <- readFile' ("templates" </> "menu.mustache")
let withIncludes = fileContent & toS & T.replace "{{>header}}" (toS header) & T.replace "{{>menu}}" (toS menu)
res = compileMustacheText "page" (toS withIncludes)
case res of
Left _ -> fail "BAD"
Right template -> return template
tocRequested :: Text -> Bool
tocRequested fc =
let toc = fc & T.lines
& map T.toLower
& filter (T.isPrefixOf (T.pack "#+options: "))
& head
& fmap (filter (T.isPrefixOf (T.pack "toc:")) . T.words)
in toc == Just ["toc:t"]
mkGetPost :: Rules (FilePath -> Action BlogPost)
mkGetPost = newCache $ \path -> do
fileContent <- readFile' path
let toc = tocRequested (toS fileContent)
eitherResult <- liftIO $ Pandoc.runIO $ Readers.readOrg (def { readerStandalone = True }) (toS fileContent)
case eitherResult of
Left _ -> fail "BAD"
Right pandoc -> getBlogpostFromMetas path toc pandoc
mkGetPosts :: (FilePath -> Action b) -> Rules (() -> Action [b])
mkGetPosts getPost =
newCache $ \() -> mapM getPost =<< getDirectoryFiles "" ["src/posts//*.org"]

View File

@ -1,8 +0,0 @@
#!/bin/sh
# mkdir -p _shake
# ghc --make app/Shakefile.hs -rtsopts -threaded -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake/build "$@"
# cabal v2-run -- her-esy-fun "$@"
runghc app/Shakefile.hs "$@"

View File

@ -5,5 +5,5 @@ echo "Watching $PWD/{src,templates}"
# fswatch --exclude='\\.#' src | while read event; do
fswatch --exclude='^.*\.#.*$' src templates | while read event; do
echo "$event"
./engine/build.sh fast
make
done

View File

@ -1,6 +1,4 @@
#!/bin/sh
#!/bin/zsh
# mkdir -p _shake
# ghc --make app/Shakefile.hs -rtsopts -threaded -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake/build "$@"
cabal v2-run -- her-esy-fun "$@"
cd "$(git rev-parse --show-toplevel)" || exit 1
make

View File

@ -1,9 +0,0 @@
#!/usr/bin/env bash
cd "$(git rev-parse --show-toplevel)" || exit 1
echo -n "* Clean site cache"
find _site -mindepth 1 -not -path "_site/.gitignore" -delete
find _full -mindepth 1 -not -path "_full/.gitignore" -delete
find _optim -mindepth 1 -not -path "_optim/.gitignore" -delete
rm -rf _cache
echo " [done]"

View File

@ -1,24 +0,0 @@
\usepackage{enumitem}
\setlistdepth{9}
\setlist[itemize,1]{label=$\bullet$}
\setlist[itemize,2]{label=$\bullet$}
\setlist[itemize,3]{label=$\bullet$}
\setlist[itemize,4]{label=$\bullet$}
\setlist[itemize,5]{label=$\bullet$}
\setlist[itemize,6]{label=$\bullet$}
\setlist[itemize,7]{label=$\bullet$}
\setlist[itemize,8]{label=$\bullet$}
\setlist[itemize,9]{label=$\bullet$}
\renewlist{itemize}{itemize}{9}
\setlist[enumerate,1]{label=$\arabic*.$}
\setlist[enumerate,2]{label=$\alph*.$}
\setlist[enumerate,3]{label=$\roman*.$}
\setlist[enumerate,4]{label=$\arabic*.$}
\setlist[enumerate,5]{label=$\alpha*$}
\setlist[enumerate,6]{label=$\roman*.$}
\setlist[enumerate,7]{label=$\arabic*.$}
\setlist[enumerate,8]{label=$\alph*.$}
\setlist[enumerate,9]{label=$\roman*.$}
\renewlist{enumerate}{enumerate}{9}

View File

@ -1,11 +0,0 @@
#!/usr/bin/env zsh
set -e # fail on first error
set -u # fail if a variable is not set
cd "$(git rev-parse --show-toplevel)" || exit 1
rootdir="${0:h}"
echo "$rootdir"
./engine/build.sh full
./engine/sync.sh

View File

@ -1,7 +0,0 @@
#!/usr/bin/env zsh
cd "$(git rev-parse --show-toplevel)" || exit 1
tmux \
new-session './engine/auto-build.sh' \; \
split-window './engine/serve.sh' \; \
split-window 'lorri watch' \; \
select-layout even-vertical

View File

@ -1,9 +0,0 @@
#!/usr/bin/env bash
cd "$(git rev-parse --show-toplevel)" || exit 1
echo "* org-publish"
emacs -nw \
--load project.el \
--eval "(progn (org-publish \"draft\") (evil-quit))"
echo "* org-publish [done]"

View File

@ -1,34 +0,0 @@
#!/usr/bin/env zsh
cd "$(git rev-parse --show-toplevel)" || exit 1
webdir="_site"
debug () {
print -- "$@" >/dev/null
}
if (($#>0)); then
filelist=( $* )
else
filelist=( $webdir/**/*.html(.) )
fi
trans(){
local suff=$1;
local fic=$2;
cat $fic | perl -p -e 's#href="?/css/mk.css"?#href=/css/'$suff'.css#;s#(/?(index|archive|slides|about-me)).html#$1-'$suff'.html#g;s#(posts/[a-zA-Z0-9_-]*).html#$1-'$suff'.html#g;s#-'$suff'.html>mk#.html>mk#g' > ${fic:r}-${suff}.html
}
print -- "Duplicate HTML by themes"
for fic in $filelist; do
if echo $fic|grep -E -- '-(mk|min|sci|modern).html$'>/dev/null; then
continue
fi
print -n -- "$fic "
for suff in sci min modern; do
trans $suff $fic
done
print "[OK]"
done
print "Duplicate HTML by theme [done]"

View File

@ -1,43 +0,0 @@
cabal-version: 2.4
name: her-esy-fun
version: 0.1.0.0
-- A short (one-line) description of the package.
-- synopsis:
-- A longer description of the package.
-- description:
-- A URL where users can report bugs.
-- bug-reports:
-- The license under which the package is released.
-- license:
author: Yann Esposito (Yogsototh)
maintainer: yann.esposito@gmail.com
-- A copyright notice.
-- copyright:
-- category:
extra-source-files: CHANGELOG.md
executable her-esy-fun
main-is: Shakefile.hs
-- Modules included in this executable, other than Main.
-- other-modules:
-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
build-depends: base ^>=4.14.1.0
, aeson
, pandoc
, pandoc-types
, shake
, data-default
, protolude
, stache
, text
, time
hs-source-dirs: app
default-language: Haskell2010

View File

@ -1,14 +1,8 @@
let
sources = import ./nix/sources.nix;
pkgs = import sources.nixpkgs {};
pkgs1909 = import (fetchTarball https://github.com/NixOS/nixpkgs/archive/19.09.tar.gz) {};
haskellDeps = ps : with ps; [
shake
pandoc
data-default
protolude
pkgs1909.haskellPackages.sws
stache
turtle
ansi-terminal
];
@ -28,9 +22,9 @@ pkgs.mkShell {
git
direnv
ghc
haskellPackages.shake
tmux
# for emacs dev
ripgrep
nodePackages.http-server
];
}

View File

@ -1,24 +0,0 @@
<input name="t" type="radio" id="b">
<input name="t" type="radio" id="l">
<input name="t" type="radio" id="d">
<input name="t" type="radio" id="g">
<div id="labels">
<div class="content">
<label for="b">book</label>&nbsp;
/&nbsp;
<label for="l">light</label>&nbsp;
<span id="logo">
<a href="/">
<svg width="5em" viewBox="0 0 64 64">
<circle cx="32" cy="32" r="30" stroke="var(--b2)" stroke-width="2" fill="var(--b03)"/>
<circle cx="32" cy="32" r="12" stroke="var(--r)" stroke-width="2" fill="var(--o)"/>
<circle cx="32" cy="32" r="6" stroke-width="0" fill="var(--y)"/>
<ellipse cx="32" cy="14" rx="14" ry="8" stroke-width="0" fill="var(--b3)"/>
</svg>
</a>
</span>&nbsp;
<label for="d">dark</label>&nbsp;
/&nbsp;
<label for="g">geek</label>
</div>
</div>

View File

@ -1,30 +0,0 @@
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="utf-8">
<meta name="viewport" content="width=device-width, initial-scale=1">
<title>{{title}}</title>
<meta name="generator" content="ystgen">
<meta name="author" content="{{author}}">
<meta name="keywords" content="{{#tags}}{{.}} {{/tags}}">
<link rel="stylesheet" href="/css/y.css"/>
<link rel="alternate" type="application/rss+xml" href="/rss.xml" />
<link rel="icon" href="/favicon.ico">
</head>
<body>
{{>header}}
<div class="main">
<div id="preamble" class="status">
<div class="content"><h1>{{title}}</h1></div>
</div>
<div id="content">
{{{ body }}}
</div>
<div id="postamble" class="status">
<div class="content">
{{>menu}}
</div>
</div>
</div>
</body>
</html>

View File

@ -1,9 +0,0 @@
<nav>
<a href="/index.html">Home</a> |
<a href="/slides.html">Slides</a> |
<a href="/about-me.html">About</a>
<span class="details"> (<a href="https://gitea.esy.fun/yogsototh">code</a>
<a href="https://espial.esy.fun/u:yogsototh">bookmarks</a>
<a href="https://espial.esy.fun/u:yogsototh/notes">notes</a>)</span> |
<a href="#preamble">↑ Top ↑</a>
</nav>

View File

@ -1,46 +0,0 @@
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="utf-8">
<meta name="viewport" content="width=device-width, initial-scale=1">
<title>$title$</title>
<meta name="author" content="$author$">
<meta name="description" content="$description$">
<meta name="keywords" content="$keywords$">
<link rel="stylesheet" href="/css/y.css"/>
<link rel="alternate" type="application/rss+xml" href="/rss.xml" />
<link rel="icon" href="/favicon.ico">
</head>
<body>
{{>header}}
<div class="main">
<div id="preamble" class="status">
<div class="content">
<h1>{{title}}</h1>
<div class="meta">
<span class="article-date">$date$</span> on
<a href="https://her.esy.fun">
<span class="author">$author$</span>'s blog</a> -
<a href="{{orgsource}}">source</a> -
<a href="{{txtsource}}">gmi</a> -
<a href="{{pdf}}">pdf</a> -
<a class="permalink" href="{{permalink}}">§permalink</a>
</div>
<div class="abstract">
$description$
</div>
</div>
</div>
<div id="content">
$body$
<br/>
<a href="{{geminiurl}}"><code>=> This article is also available on gemini</code></a>
</div>
<div id="postamble" class="status">
<div class="content">
{{>menu}}
</div>
</div>
</div>
</body>
</html>

View File

@ -1,45 +0,0 @@
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="utf-8">
<meta name="viewport" content="width=device-width, initial-scale=1">
<title>{{title}}</title>
<meta name="author" content="{{author}}">
<meta name="description" content="{{description}}">
<meta name="keywords" content="{{#tags}}{{.}}{{^last}} {{/last}}{{/tags}}">
<link rel="stylesheet" href="/css/y.css"/><link rel="alternate" type="application/rss+xml" href="/rss.xml" /><link rel="icon" href="/favicon.ico">
<link rel="stylesheet" href="/css/slides.css"/><link rel="alternate" type="application/rss+xml" href="/rss.xml" /><link rel="icon" href="/favicon.ico">
</head>
<body>
{{>header}}
<div class="main">
<div id="preamble" class="status">
<div class="content">
<h1>{{title}}</h1>
<div class="meta">
<span class="article-date">{{date}}</span> on
<a href="https://her.esy.fun">
<span class="author">{{author}}</span>'s blog</a> -
<a href="{{orgsource}}">source</a> -
<a href="{{txtsource}}">txt</a> -
<a href="{{pdf}}">pdf</a> -
<a class="permalink" href="{{permalink}}">§permalink</a>
</div>
<div class="abstract">
{{description}}
</div>
</div>
</div>
<div id="content">
{{{body}}}
<br/>
<a href="{{geminiurl}}"><code>=> This article is also available on gemini</code></a>
</div>
<div id="postamble" class="status">
<div class="content">
{{>menu}}
</div>
</div>
</div>
</body>
</html>