{-# LANGUAGE OverloadedStrings #-} -- | The main deployment script. module Main where import Control.Monad (unless, when) import Control.Monad.Trans.State.Lazy import qualified Data.Aeson.KeyMap as KM import qualified Data.ByteString.Lazy as B import Data.Digest.Pure.SHA (sha256, showDigest) import Data.Foldable (traverse_) import Data.List (nub) import qualified Data.Map as M import qualified Data.Set as S import Data.String (fromString) import qualified Data.Text as T import qualified Data.Text.Encoding import qualified Data.Text.IO as TIO import qualified Data.Yaml as Y import Hakyll.Core.Util.File (getRecursiveContents, makeDirectories) import Lens.Micro import Lens.Micro.Aeson import Lens.Micro.Mtl import System.FilePath ((), splitPath, takeFileName) import qualified Text.Mustache as Mu import Text.Pandoc.Class (runIOorExplode) import Text.Pandoc.Readers.Markdown (readMarkdown) import Text.Pandoc.Writers.HTML (writeHtml5String) import qualified Text.Parsec.Error import FormatOpts import Types import Utils -- | Load the pages from a directory and add them to `pages`. sourcePages :: FilePath -> Site () sourcePages fp = do links <- io $ filter (hasSuffix ".md" . last . splitPath) <$> getRecursiveContents (pure . const False) fp traverse_ loadPage (map (fp ) links) {- | Extract `PageInfo` about a single page and save it into `pages` in - `SiteState`. -} loadPage :: FilePath -> Site () loadPage fp = do io $ putStrLn $ "P <- " ++ fp txt <- io $ TIO.readFile fp {- tear out the metadata manually -} (T.take 4 txt == "---\n") `unless` error ("metadata block start missing in " ++ fp) let (meta, markdown) = T.breakOn "\n---\n" (T.drop 4 txt) T.null meta `when` error ("metadata block bad in " ++ fp) {- parse everything -} yml <- Y.decodeThrow $ Data.Text.Encoding.encodeUtf8 meta md <- io $ runIOorExplode $ readMarkdown markdownReadOpts (T.drop 5 markdown) {- find the main mount point for the page -} let mount = T.unpack . just ("mount point of " ++ fp) $ yml ^? key "title" . _String {- save to the state -} pages %= M.insert mount PageInfo {_pagePath = fp, _pageMeta = yml, _pageDoc = md} -- | Find which template to use for rendering a page. pageTemplate :: PageInfo -> Site FilePath pageTemplate pi = do dt <- use defaultTemplate pure . maybe dt T.unpack $ pi ^? pageMeta . key "template" . _String -- | Collect all templates required for rendering the currently loaded pages. pageTemplates :: Site [FilePath] pageTemplates = do rt <- use redirectTemplate nub . (rt :) <$> (gets (^.. pages . traverse) >>= traverse pageTemplate) compileTemplate :: FilePath -> FilePath -> Site (Either Text.Parsec.Error.ParseError Mu.Template) compileTemplate templdir templ = io $ do putStrLn $ "T <- " ++ (templdir templ) Mu.automaticCompile [templdir] templ -- | Use a template set from a given directory. sourceTemplates :: FilePath -> Site () sourceTemplates templdir = do ts <- pageTemplates templs' <- fmap sequence . traverse (compileTemplate templdir) $ ts case templs' of Left err -> error $ "template compilation: " ++ show err Right templs -> templates .= M.fromList (zip ts templs) -- | Find the path to the "index.html" of a given mount. indexFilename :: FilePath -> Site FilePath indexFilename mount = do od <- use outputDir pure (od mount "index.html") -- | Check that the page was not rendered before, and add it to the rendered set checkTarget :: FilePath -> Site () checkTarget fp = do found <- S.member fp <$> use targets if found then error $ "colliding renders for page: " ++ fp else targets %= S.insert fp -- | Render a page using the current template. installPage :: FilePath -> PageInfo -> Site () installPage mount pi {- find the correct template and metadata -} = do tname <- pageTemplate pi templ <- use $ templates . to (M.! fromString tname) file <- indexFilename mount checkTarget file io $ do putStrLn $ "P -> " ++ file makeDirectories file body <- runIOorExplode $ writeHtml5String htmlWriteOpts (pi ^. pageDoc) let Y.Object meta' = pi ^. pageMeta meta = Y.Object $ KM.insert "body" (Y.String body) meta' TIO.writeFile file $ Mu.substitute templ meta {- | Install a simple redirect handler page. -} installRedirect :: FilePath -> FilePath -> Site () installRedirect target from = do tname <- use redirectTemplate templ <- use $ templates . to (M.! fromString tname) file <- indexFilename from checkTarget file io $ do putStrLn $ "@ -> " ++ file ++ " -> " ++ target makeDirectories file TIO.writeFile file . Mu.substitute templ $ Y.object [("target", Y.String $ T.pack target)] -- | Install all redirects required by one page. installPageRedirects :: FilePath -> PageInfo -> Site () installPageRedirects target pi = do traverse_ (installRedirect target . T.unpack) (pi ^.. pageMeta . key "redirects" . values . _String) -- | Install all redirects required by all pages. installRedirects :: Site () installRedirects = use pages >>= traverse_ (uncurry installPageRedirects) . M.assocs -- | Find the path to the file of a given hash dataFilename :: String -> FilePath -> Site (FilePath, FilePath) dataFilename hash basename = do od <- use outputDir let (h1, h2) = splitAt 3 hash loc = "data" h1 h2 basename pure (od loc, loc) {- | Install a file. Files are installed into a single shared location. That - prevents file duplication and also gives a bit of control for where the - files reside and what are their names. -} installFile :: FilePath -> Site FilePath installFile fp = do let basename = takeFileName fp hash <- showDigest . sha256 <$> io (B.readFile fp) alreadyExists <- S.member hash <$> use installs (file, loc) <- dataFilename hash basename unless alreadyExists $ do installs %= S.insert hash checkTarget file io $ do putStrLn $ "F -> " ++ fp ++ " -> " ++ file makeDirectories file B.readFile fp >>= B.writeFile file pure loc -- | Simply copy a strictly named asset. installAsset :: FilePath -> Site () installAsset fp = undefined -- | Render a site for a given tag string. renderTag :: [String] -> Site () renderTag = undefined -- | Render all tag sites. renderTags :: Site () renderTags = undefined -- | Build the whole site. main = flip runStateT emptySiteState $ do traverse sourcePages ["external"] sourceTemplates "templates" use pages >>= traverse (uncurry installPage) . M.assocs installRedirects installFile "external/mypage/img/awesome.png" io $ putStrLn "OK" get >>= io . print