Revamp:
- Switch from `cabal2nix` and haskell overlay to `developPackage` - Restructure directories to have more descriptive names - Fix `nix run`
This commit is contained in:
71
static-site-generator/Formats/Gogen.hs
Normal file
71
static-site-generator/Formats/Gogen.hs
Normal file
@@ -0,0 +1,71 @@
|
||||
{-# LANGUAGE QuasiQuotes, FlexibleContexts #-}
|
||||
|
||||
module Formats.Gogen (gogenCtx) where
|
||||
|
||||
import Hakyll
|
||||
import Debug.Trace (traceId)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Control.Applicative (empty)
|
||||
import Text.Regex.PCRE.Heavy (Regex, gsub, re)
|
||||
|
||||
import Util.Hakyll.Context
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- FURIGANA CONVERSION
|
||||
|
||||
type FuriganaTemplate = String
|
||||
|
||||
convertTitle :: (String -> String) -> Item a -> Compiler String
|
||||
convertTitle = updateFieldWith "title" "???"
|
||||
|
||||
furiganaRegex :: Regex
|
||||
furiganaRegex = [re|\[(.*?)\]\((.*?)\)|]
|
||||
|
||||
replaceFuriganaWithKanji :: FuriganaTemplate -> String
|
||||
replaceFuriganaWithKanji = gsub furiganaRegex (\(kanji:_) -> kanji :: String)
|
||||
|
||||
replaceFuriganaWithHtml :: FuriganaTemplate -> String
|
||||
replaceFuriganaWithHtml = between "<ruby>" "</ruby>" . gsub furiganaRegex matchToHtml
|
||||
where
|
||||
between :: String -> String -> String -> String
|
||||
between x y s = x ++ s ++ y
|
||||
|
||||
matchToHtml :: [String] -> String
|
||||
matchToHtml (kanji:kana:_) =
|
||||
let defaultKanji = if kanji == "" then "〇" else kanji
|
||||
in foldr1 (++) ["<rb>", defaultKanji, "</rb> <rp>(</rp><rt>", kana, "</rt><rp>)</rp>"]
|
||||
|
||||
convertFuriganaTitle :: Item a -> Compiler String
|
||||
convertFuriganaTitle = convertTitle replaceFuriganaWithKanji
|
||||
|
||||
convertFuriganaTitleHtml :: Item a -> Compiler String
|
||||
convertFuriganaTitleHtml = convertTitle replaceFuriganaWithHtml
|
||||
|
||||
convertFinishedValue :: Item a -> Compiler ContextField
|
||||
convertFinishedValue i = do
|
||||
s <- getMetadataField (itemIdentifier i) "finished"
|
||||
case s of
|
||||
Just "true" -> empty
|
||||
_ -> return (StringField "true")
|
||||
|
||||
{- |
|
||||
title: String
|
||||
titleHtml: String
|
||||
finished: Boolean
|
||||
updated: String
|
||||
lang: String
|
||||
antonyms: Maybe [String]
|
||||
synonyms: Maybe [String]
|
||||
leads_here: Maybe [String]
|
||||
alternatives: Maybe [String]
|
||||
see_also: Maybe [String]
|
||||
sources: Maybe [String]
|
||||
-}
|
||||
gogenCtx :: Context String
|
||||
gogenCtx =
|
||||
dateField "date" "%Y-%m-%d"
|
||||
<> ifField "notFinishedYet" convertFinishedValue
|
||||
<> field "title" convertFuriganaTitle
|
||||
<> field "titleHtml" convertFuriganaTitleHtml
|
||||
<> constField "lang" "en"
|
||||
<> defaultContext
|
||||
13
static-site-generator/Formats/Posts.hs
Normal file
13
static-site-generator/Formats/Posts.hs
Normal file
@@ -0,0 +1,13 @@
|
||||
module Formats.Posts where
|
||||
|
||||
import Hakyll
|
||||
import Util.Hakyll.Routes
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Util.Hash (FileHashes)
|
||||
import Debug.Trace
|
||||
|
||||
postRoute :: FileHashes -> Routes
|
||||
postRoute hashes = titleRouteElseHash `composeRoutes` prefixRoute "posts/"
|
||||
where
|
||||
titleRouteElseHash :: Routes
|
||||
titleRouteElseHash = metadataRoute $ \metadata -> fromMaybe (hashRoute hashes) $ titleRoute metadata
|
||||
Reference in New Issue
Block a user