initial work this'll take awhile
This commit is contained in:
parent
23d688642a
commit
e36bc359ca
3 changed files with 74 additions and 0 deletions
67
Site.hs
Executable file
67
Site.hs
Executable file
|
@ -0,0 +1,67 @@
|
||||||
|
#! /usr/bin/env nix-shell
|
||||||
|
#! nix-shell -p "haskellPackages.ghcWithPackages (p: [p.mustache p.pandoc p.shake p.deriving-aeson])"
|
||||||
|
#! nix-shell -i runhaskell
|
||||||
|
|
||||||
|
-- pulling heavily from https://abhinavsarkar.net/posts/static-site-generator-using-shake/
|
||||||
|
-- docs:
|
||||||
|
-- https://hackage.haskell.org/package/pandoc-3.2.1/docs/doc-index-All.html
|
||||||
|
-- https://hackage.haskell.org/package/mustache-2.4.2/docs/doc-index.html
|
||||||
|
--
|
||||||
|
{-# LANGUAGE ApplicativeDo, DataKinds, DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE DerivingVia, LambdaCase, TypeApplications #-}
|
||||||
|
|
||||||
|
module Main where
|
||||||
|
|
||||||
|
import Control.Monad (forM, void)
|
||||||
|
import Data.Aeson.Types (Result (..))
|
||||||
|
import Data.List (nub, sortOn)
|
||||||
|
import Data.Text (Text)
|
||||||
|
import Data.Time (UTCTime, defaultTimeLocale, formatTime, parseTimeM)
|
||||||
|
import Deriving.Aeson
|
||||||
|
import Deriving.Aeson.Stock (PrefixedSnake)
|
||||||
|
import Development.Shake (Action, Rules, (%>), (|%>), (~>))
|
||||||
|
import Development.Shake.FilePath ((<.>), (</>))
|
||||||
|
import Text.Pandoc (Block (Plain), Meta (..), MetaValue (..), Pandoc (..))
|
||||||
|
import qualified Data.Aeson.Types as A
|
||||||
|
import qualified Data.HashMap.Strict as HM
|
||||||
|
import qualified Data.Ord as Ord
|
||||||
|
import qualified Data.Text as T
|
||||||
|
import qualified Development.Shake as Shake
|
||||||
|
import qualified Development.Shake.FilePath as Shake
|
||||||
|
import qualified Text.Mustache as Mus
|
||||||
|
import qualified Text.Mustache.Compile as Mus
|
||||||
|
import qualified Text.Pandoc as Pandoc
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = Shake.shakeArgs Shake.shakeOptions $ do
|
||||||
|
Shake.withTargetDocs "Build the site" $
|
||||||
|
"build" ~> buildTargets
|
||||||
|
Shake.withTargetDocs "Clean the built site" $
|
||||||
|
"clean" ~> Shake.removeFilesAfter outputDir ["//*"]
|
||||||
|
|
||||||
|
outputDir :: String
|
||||||
|
outputDir = "publish"
|
||||||
|
|
||||||
|
buildTargets :: Action ()
|
||||||
|
buildTargets = do
|
||||||
|
assetPaths <- Shake.getDirectoryFiles "" assetGlobs
|
||||||
|
|
||||||
|
typstToHtml :: FilePath -> Action Text
|
||||||
|
typstToHtml filePath = do
|
||||||
|
content <- Shake.readFile' filePath
|
||||||
|
Shake.quietly . Shake.traced "Typst to HTML" $ do
|
||||||
|
doc <- runPandoc . Pandoc.readTypst readerOptions . T.pack $ content
|
||||||
|
|
||||||
|
runPandoc . Pandoc.writeHtml5String writerOptions $ doc
|
||||||
|
where
|
||||||
|
readerOptions =
|
||||||
|
Pandoc.def {Pandoc.readerExtensions = Pandoc.pandocExtensions}
|
||||||
|
writerOptions =
|
||||||
|
Pandoc.def {Pandoc.writerExtensions = Pandoc.pandocExtensions}
|
||||||
|
|
||||||
|
assetGlobs :: [String]
|
||||||
|
assetGlobs = ["css/*.css", "images/*.png"]
|
||||||
|
|
||||||
|
runPandoc action =
|
||||||
|
Pandoc.runIO (Pandoc.setVerbosity Pandoc.ERROR >> action)
|
||||||
|
>>= either (fail . show) return
|
1
notes
1
notes
|
@ -16,3 +16,4 @@ https://fonts.google.com/knowledge/choosing_type/pairing_typefaces_within_a_fami
|
||||||
noted fonts:
|
noted fonts:
|
||||||
https://fonts.google.com/specimen/Marcellus?preview.size=79&stroke=Serif
|
https://fonts.google.com/specimen/Marcellus?preview.size=79&stroke=Serif
|
||||||
https://fonts.google.com/specimen/Tinos?preview.size=79&stroke=Serif
|
https://fonts.google.com/specimen/Tinos?preview.size=79&stroke=Serif
|
||||||
|
https://fonts.google.com/noto/specimen/Noto+Serif+Display?classification=Display&stroke=Serif&stylecount=18&preview.text=Hello%20there
|
||||||
|
|
6
pages/links.typ
Normal file
6
pages/links.typ
Normal file
|
@ -0,0 +1,6 @@
|
||||||
|
#import misc_page from "/utils/layouts"
|
||||||
|
#wrap doc in misc_page(doc)
|
||||||
|
|
||||||
|
#link("https://github.com/Pagwin-Fedora")[Github] \
|
||||||
|
#link("https://www.linkedin.com/in/spencer-powell-pagwin/")[Linkedin] \
|
||||||
|
#link("https://pagwin.xyz/index.xml")[RSS]
|
Loading…
Reference in a new issue