just need to turn template application into application+write or do something else

This commit is contained in:
Pagwin 2024-07-22 17:17:23 -04:00
parent 2dc9cb3dc6
commit a15d27a324
No known key found for this signature in database
GPG key ID: 81137023740CA260

View file

@ -9,13 +9,16 @@
module Main where module Main where
import Control.Monad (forM)
import Data.List (sortOn)
import Data.Text (Text) import Data.Text (Text)
import Data.Time (UTCTime, defaultTimeLocale, formatTime, parseTimeM) import Data.Time (UTCTime, defaultTimeLocale, formatTime, parseTimeM)
import Deriving.Aeson import Deriving.Aeson
import Deriving.Aeson.Stock (PrefixedSnake) import Deriving.Aeson.Stock (PrefixedSnake)
import Development.Shake (Action, Rules, (|%>), (~>)) import Development.Shake (Action, Rules, (|%>), (~>), (%>))
import Development.Shake.FilePath ((</>)) import Development.Shake.FilePath ((</>))
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
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 Shake
@ -53,9 +56,11 @@ buildSite = do
buildRules :: Rules () buildRules :: Rules ()
buildRules = do buildRules = do
home
assets assets
pages pages
posts posts
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 ()
@ -97,6 +102,27 @@ posts = 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
home :: Rules ()
home = outputDir </> "index.html" %> \target -> do
postPaths <- Shake.getDirectoryFiles "" postGlobs
posts <- take 3
. sortOn (Ord.Down . postDate)
<$> forM postPaths readPost
html <- applyTemplate "home.html" $ HM.singleton "posts" posts
let page = Page (T.pack "Home") html
applyTemplateAndWrite "default.html" page target
Shake.putInfo $ "Built " <> target
rss :: Rules ()
rss = outputDir </> "index.xml" %> \target -> do
postPaths <- Shake.getDirectoryFiles "" postGlobs
posts <- sortOn (Ord.Down . postDate) <$> forM postPaths readPost
-- figure out how to convert this into applyTemplateAndWrite
feed <- applyTemplate "feed.xml" $ HM.singleton "posts" posts
Shake.putInfo $ "Built " <> target
readPost :: FilePath -> Action Post readPost :: FilePath -> Action Post
readPost postPath = do readPost postPath = do
date <- parseTimeM False defaultTimeLocale "%Y-%-m-%-d" date <- parseTimeM False defaultTimeLocale "%Y-%-m-%-d"