Revamp:
- Switch from `cabal2nix` and haskell overlay to `developPackage` - Restructure directories to have more descriptive names - Fix `nix run`
This commit is contained in:
22
static-site-generator/Preprocessing/Graphviz.hs
Normal file
22
static-site-generator/Preprocessing/Graphviz.hs
Normal file
@@ -0,0 +1,22 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Preprocessing.Graphviz where
|
||||
|
||||
import Data.Text (Text, pack, unpack)
|
||||
import System.Process ( readProcess )
|
||||
import Text.Pandoc
|
||||
( Pandoc,
|
||||
Block (RawBlock, CodeBlock),
|
||||
Format (Format),
|
||||
)
|
||||
|
||||
codeBlock :: Block -> IO Block
|
||||
codeBlock cb@(CodeBlock (id, classes, namevals) contents)
|
||||
| "dot" `elem` classes = RawBlock (Format "html") . pack <$> svg (unpack contents)
|
||||
| otherwise = return cb
|
||||
codeBlock x = return x
|
||||
|
||||
svg :: String -> IO String
|
||||
svg = readProcess "dot" ["-Tsvg"]
|
||||
|
||||
-- PlantUML
|
||||
120
static-site-generator/Preprocessing/LogoLinks.hs
Normal file
120
static-site-generator/Preprocessing/LogoLinks.hs
Normal file
@@ -0,0 +1,120 @@
|
||||
{-# LANGUAGE QuasiQuotes, FlexibleContexts #-}
|
||||
module Preprocessing.LogoLinks where
|
||||
|
||||
import Hakyll
|
||||
import Text.Regex.PCRE.Heavy (Regex, re, gsub)
|
||||
import Debug.Trace
|
||||
|
||||
type Html = String
|
||||
type LLConverter = String -> String -> Html
|
||||
|
||||
replaceLogoLinks :: Item String -> Compiler (Item String)
|
||||
replaceLogoLinks = return . fmap replaceAllLogoLinks
|
||||
|
||||
|
||||
fullLogoLinkRegex :: Regex
|
||||
fullLogoLinkRegex = [re|\[(.*?)\|(.*?)\]\((.*?)\)|]
|
||||
|
||||
shortLogoLinkRegex :: Regex
|
||||
shortLogoLinkRegex = [re|\[(.*?)\|(.*?)\](?!\()|]
|
||||
|
||||
replaceAllLogoLinks :: Html -> Html
|
||||
replaceAllLogoLinks = gsub fullLogoLinkRegex f . gsub shortLogoLinkRegex g
|
||||
where
|
||||
g (key:s1:_)
|
||||
| key == "gh" = github s1 ("https://github.com/" ++ s1)
|
||||
| key == "gl" = gitlab s1 ("https://gitlab.com/" ++ s1)
|
||||
| key == "ga" = gitea s1 ("https://gitea.com/" ++ s1)
|
||||
| key == "nani" = nani s1 ("https://git.nani.wtf/" ++ s1)
|
||||
| key == "pub" = pub s1 ("https://pub.dev/packages/" ++ s1)
|
||||
| key == "nxp" = nixpackages s1 ("https://search.nixos.org/packages?query=" ++ s1)
|
||||
| key == "nxo" = nixoptions s1 ("https://search.nixos.org/options?query=" ++ s1)
|
||||
| key == "npm" = npm s1 ("https://www.npmjs.com/package/" ++ s1)
|
||||
| key == "crt" = crates s1 ("https://crates.io/crates/" ++ s1)
|
||||
| key == "hk" = hackage s1 ("https://hackage.haskell.org/package/" ++ s1)
|
||||
| key == "hg" = hoogle s1 ("https://hoogle.haskell.org/?hoogle=" ++ s1)
|
||||
| key == "yt" = youtube s1 ("https://www.youtube.com/embed/" ++ s1)
|
||||
-- Reconstruct the original text
|
||||
| otherwise = foldr1 (++) ["[", key, "|", s1, "]"]
|
||||
|
||||
f (key:s1:s2:_)
|
||||
| key == "kan" = kan s1 s2
|
||||
| key == "so" = stackoverflow s1 s2
|
||||
| key == "rd" = reddit s1 s2
|
||||
| key == "wiki" = wikipedia s1 s2
|
||||
| key == "jisho" = jisho s1 s2
|
||||
-- Reconstruct the original text
|
||||
| otherwise = foldr1 (++) ["[", key, "|", s1, "](", s2, ")"]
|
||||
|
||||
{- This should be removed once all icons are added, and all functions are implemented -}
|
||||
generateGenericLink :: String -> LLConverter
|
||||
generateGenericLink linkTitle = f
|
||||
where
|
||||
f name link = foldr1 (++) ["<a href=\"", link, "\">", linkTitle, ": ", name, "</a>"]
|
||||
|
||||
|
||||
badgeLinkWithCustomClasses :: String -> [String] -> LLConverter
|
||||
badgeLinkWithCustomClasses imageName classes = f
|
||||
where
|
||||
f name link = foldr1 (++) [
|
||||
"<span class='bg-dark rounded-3 my-1 px-2 py-1 position-relative nani_logo-link " ++ unwords classes ++ "'>",
|
||||
"<img src='/images/logos/" ++ imageName ++ "' class='card-img-left me-2' alt='GitHub Logo'>",
|
||||
"<span class='text-light'>" ++ name ++ "</span>",
|
||||
"<a href='" ++ link ++ "' class='stretched-link'></a>",
|
||||
"</span>"
|
||||
]
|
||||
|
||||
badgeLink :: String -> LLConverter
|
||||
badgeLink imageName = badgeLinkWithCustomClasses imageName []
|
||||
|
||||
|
||||
kan :: LLConverter
|
||||
kan kanji kana = foldr1 (++) ["<ruby><rb>", kanji, "</rb> <rp>(</rp><rt>", kana, "</rt><rp>)</rp></ruby>"]
|
||||
|
||||
github :: LLConverter
|
||||
github = badgeLink "github.svg"
|
||||
|
||||
gitlab :: LLConverter
|
||||
gitlab = badgeLink "gitlab.svg"
|
||||
|
||||
gitea :: LLConverter
|
||||
gitea = badgeLink "gitea.svg"
|
||||
|
||||
nani :: LLConverter
|
||||
nani = badgeLink "nani.svg"
|
||||
|
||||
stackoverflow :: LLConverter
|
||||
stackoverflow = badgeLink "stack_overflow.svg"
|
||||
|
||||
pub :: LLConverter
|
||||
pub = badgeLink "dart.svg"
|
||||
|
||||
hoogle :: LLConverter
|
||||
hoogle = badgeLink "haskell_orange.svg"
|
||||
|
||||
crates :: LLConverter
|
||||
crates = badgeLinkWithCustomClasses "rust.svg" ["nani_logo-link-color-inverted"]
|
||||
|
||||
hackage :: LLConverter
|
||||
hackage = badgeLink "haskell_purple.svg"
|
||||
|
||||
nixpackages :: LLConverter
|
||||
nixpackages = badgeLink "nix_packages.svg"
|
||||
|
||||
nixoptions :: LLConverter
|
||||
nixoptions = badgeLink "nix_options.svg"
|
||||
|
||||
npm :: LLConverter
|
||||
npm = badgeLink "npm.svg"
|
||||
|
||||
reddit :: LLConverter
|
||||
reddit = badgeLink "reddit.svg"
|
||||
|
||||
wikipedia :: LLConverter
|
||||
wikipedia = badgeLinkWithCustomClasses "wikipedia.svg" ["nani_logo-link-color-inverted"]
|
||||
|
||||
youtube :: LLConverter
|
||||
youtube _ link = "<div class='nani_youtube'><iframe src='" ++ link ++ "' frameborder='0' allowfullscreen></iframe></div>"
|
||||
|
||||
jisho :: LLConverter
|
||||
jisho name link = undefined
|
||||
Reference in New Issue
Block a user