markdown and typst aren't fighting but for some reason the markdown isn't pulling the metadata

This commit is contained in:
Pagwin 2024-08-17 19:52:09 -04:00
parent 80970cc18c
commit db24be34dd
No known key found for this signature in database
GPG key ID: 81137023740CA260
2 changed files with 47 additions and 27 deletions

View file

@ -7,7 +7,7 @@
module Main where module Main where
import Control.Monad (forM) import Control.Monad (forM, when)
import Data.List (sortOn) import Data.List (sortOn)
import Development.Shake (Action, Rules, (|%>), (~>), (%>)) import Development.Shake (Action, Rules, (|%>), (~>), (%>))
import Development.Shake.FilePath ((</>)) import Development.Shake.FilePath ((</>))
@ -15,7 +15,7 @@ import qualified Data.HashMap.Strict as HM
import qualified Data.Ord as Ord import qualified Data.Ord as Ord
import qualified Data.Text as T import qualified Data.Text as T
import qualified Development.Shake as Shake import qualified Development.Shake as Shake
import qualified Development.Shake.FilePath as Shake import qualified Development.Shake.FilePath as FP
import Config import Config
import Types import Types
import Utilities import Utilities
@ -26,7 +26,8 @@ import Data.Time
-- Action = actions to produce a thing -- Action = actions to produce a thing
main :: IO () main :: IO ()
main = Shake.shakeArgs Shake.shakeOptions $ do main = do
Shake.shakeArgs Shake.shakeOptions $ do
Shake.withTargetDocs "Build the site" $ Shake.withTargetDocs "Build the site" $
"build" ~> buildSite "build" ~> buildSite
Shake.withTargetDocs "Clean the built site" $ Shake.withTargetDocs "Clean the built site" $
@ -55,14 +56,13 @@ buildRules = do
home home
assets assets
pages pages
typstPostsRule postsRule
markdownPostsRule
rss rss
-- make a rule of the pattern outputDir/asset_name which copes from outputDir/../pages -- make a rule of the pattern outputDir/asset_name which copes from outputDir/../pages
assets :: Rules () assets :: Rules ()
assets = map (outputDir </>) assetGlobs |%> \target -> do assets = map (outputDir </>) assetGlobs |%> \target -> do
let src = Shake.dropDirectory1 target let src = FP.dropDirectory1 target
Shake.copyFileChanged src target Shake.copyFileChanged src target
Shake.putInfo $ "Copied " <> target <> " from " <> src Shake.putInfo $ "Copied " <> target <> " from " <> src
@ -77,9 +77,25 @@ pages = map indexHtmlOutputPath pagePaths |%> \target -> do
applyTemplateAndWrite "default.html" page target applyTemplateAndWrite "default.html" page target
Shake.putInfo $ "Built " <> target <> " from " <> src Shake.putInfo $ "Built " <> target <> " from " <> src
typstPostsRule :: Rules () -- there's probably a better way of doing this that allows for the target's origin file extension to get passed in but for now we're doing brute force
typstPostsRule = map indexHtmlOutputPath postGlobs |%> \target -> do postsRule :: Rules ()
let src = indexHtmlTypstSourcePath target postsRule = map indexHtmlOutputPath postGlobs |%> \target -> do
let potentials = indexHtmlSourcePaths target
Shake.forP potentials (\path->do
exists <- Shake.doesFileExist path
when exists
(case FP.takeExtension path of
".typ" -> typstPost path
".md" -> markdownPost path
_ -> error $ "invalid file extension for post " <> target)
)
return ()
typstPost :: FP.FilePath -> Action ()
typstPost src = do
Shake.need [src]
let target = indexHtmlOutputPath src
post <- readTypstPost src post <- readTypstPost src
postHtml <- applyTemplate "post.html" post postHtml <- applyTemplate "post.html" post
@ -87,9 +103,12 @@ typstPostsRule = map indexHtmlOutputPath postGlobs |%> \target -> do
applyTemplateAndWrite "default.html" page target applyTemplateAndWrite "default.html" page target
Shake.putInfo $ "Built " <> target <> " from " <> src Shake.putInfo $ "Built " <> target <> " from " <> src
markdownPostsRule :: Rules ()
markdownPostsRule = map indexHtmlOutputPath postGlobs |%> \target -> do markdownPost :: FP.FilePath -> Action ()
let src = indexHtmlMarkdownSourcePath target markdownPost src = do
Shake.need [src]
let target = indexHtmlOutputPath src
post <- readMarkdownPost src post <- readMarkdownPost src
postHtml <- applyTemplate "post.html" post postHtml <- applyTemplate "post.html" post
@ -119,7 +138,7 @@ rss = outputDir </> "index.xml" %> \target -> do
readPost :: FilePath -> Action Post readPost :: FilePath -> Action Post
readPost postPath = do readPost postPath = do
case Shake.takeExtension postPath of case FP.takeExtension postPath of
".typ" -> readTypstPost postPath ".typ" -> readTypstPost postPath
".md" -> readMarkdownPost postPath ".md" -> readMarkdownPost postPath
_ -> error $ "unknown file extension for file" <> postPath _ -> error $ "unknown file extension for file" <> postPath
@ -132,20 +151,15 @@ readTypstPost postPath = do
return $ post return $ post
{ {
postContent = Just html, postContent = Just html,
postLink = Just . T.pack $ "/" <> Shake.dropExtension postPath <> "/" postLink = Just . T.pack $ "/" <> FP.dropExtension postPath <> "/"
} }
readMarkdownPost :: FilePath -> Action Post readMarkdownPost :: FilePath -> Action Post
readMarkdownPost postPath = do readMarkdownPost postPath = do
date <- parseTimeM False defaultTimeLocale "%Y-%-m-%-d"
. take 10
. Shake.takeBaseName
$ postPath
let formattedDate = T.pack $ formatTime @UTCTime defaultTimeLocale "%b %e, %Y" date
(post, html) <- markdownToHtml postPath (post, html) <- markdownToHtml postPath
Shake.putInfo $ "Read " <> postPath Shake.putInfo $ "Read " <> postPath
return $ post return $ post
{ postDate = Just formattedDate, {
postContent = Just html, postContent = Just html,
postLink = Just . T.pack $ "/" <> Shake.dropExtension postPath <> "/" postLink = Just . T.pack $ "/" <> FP.dropExtension postPath <> "/"
} }

View file

@ -109,3 +109,9 @@ yamlToPost path = do
dateStrTransform date = do dateStrTransform date = do
date' <- parseTimeM False defaultTimeLocale "%Y-%-m-%-d" date date' <- parseTimeM False defaultTimeLocale "%Y-%-m-%-d" date
Just $ T.pack $ formatTime @UTCTime defaultTimeLocale "%b %e, %Y" date' Just $ T.pack $ formatTime @UTCTime defaultTimeLocale "%b %e, %Y" date'
isTypstPost :: FilePath -> Bool
isTypstPost path = Shake.takeExtension path == ".typ"
isMarkdownPost :: FilePath -> Bool
isMarkdownPost path = Shake.takeExtension path == ".md"