- Switch from `cabal2nix` and haskell overlay to `developPackage`
- Restructure directories to have more descriptive names
- Fix `nix run`
This commit is contained in:
2023-03-11 16:51:23 +01:00
parent 669ded6d45
commit dcdf36f4dd
104 changed files with 51 additions and 232 deletions

View File

@@ -0,0 +1,43 @@
module Util.Hakyll.Context (
updateFieldWith,
defaultConstField,
ifField,
) where
import Hakyll
import Data.Maybe (fromMaybe)
import Control.Applicative (empty)
{- |
Shortcut function for getting an Items Metadata
This is used as a helper function in a lot of places.
-}
getItemMetadata :: Item a -> Compiler Metadata
getItemMetadata = getMetadata . itemIdentifier
{- |
-}
updateFieldWith :: String -> String -> (String -> String) -> Item a -> Compiler String
updateFieldWith field defaultPreviousValue f =
fmap updateField . getMetadata . itemIdentifier
where
updateField :: Metadata -> String
updateField = f . fromMaybe defaultPreviousValue . lookupString field
{- |
This function takes a field name, and a default String value.
If the field is found, it will leave it be, else inject the default value.
Similar to the behaviour of (fromMaybe)
-}
defaultConstField :: String -> String -> Context String
defaultConstField fieldString defaultValue =
field fieldString (fmap f . getItemMetadata)
where
f :: Metadata -> String
f = fromMaybe defaultValue . lookupString fieldString
{-
-}
ifField :: String -> (Item a -> Compiler ContextField) -> Context a
ifField key value = Context $ \k _ i -> if k == key then value i else empty

View File

@@ -0,0 +1,47 @@
{-# LANGUAGE OverloadedStrings #-}
module Util.Hakyll.Routes where
import Hakyll
import Data.Maybe (fromMaybe)
import Data.Map as Map
import qualified Data.Text as T
import qualified Data.Text.Slugger as Slugger
import Debug.Trace
import Util.Hash (FileHashes)
prefixRoute :: FilePath -> Routes
prefixRoute p = customRoute $ \id' -> p ++ toFilePath id'
titleRouteWithDefault :: String -> Metadata -> Routes
titleRouteWithDefault defaultValue = constRoute . fileNameFromTitle
where
getTitleFromMeta :: Metadata -> String
getTitleFromMeta =
fromMaybe defaultValue . lookupString "title"
fileNameFromTitle :: Metadata -> FilePath
fileNameFromTitle =
T.unpack . (`T.append` ".html") . Slugger.toSlug . T.pack . getTitleFromMeta
titleRoute :: Metadata -> Maybe Routes
titleRoute metadata = constRoute <$> fileNameFromTitle metadata
where
slug :: String -> String
slug = T.unpack . (`T.append` ".html") . Slugger.toSlug . T.pack
ignore :: Eq a => a -> a -> Maybe a
ignore shouldBeIgnored value
| shouldBeIgnored == value = Nothing
| otherwise = Just value
fileNameFromTitle :: Metadata -> Maybe FilePath
fileNameFromTitle metadata = slug <$> (ignore "" =<< lookupString "title" metadata)
hashRoute :: FileHashes -> Routes
hashRoute hashes = customRoute hash
where
hash :: Identifier -> String
hash = flip (++) ".html" . fromMaybe "error" . flip Map.lookup hashes