nani.wtf/ssg/src/Formats/Naritachi.hs

52 lines
1.8 KiB
Haskell
Raw Normal View History

2022-03-19 00:59:36 +01:00
{-# LANGUAGE QuasiQuotes, FlexibleContexts #-}
module Formats.Naritachi (
convertFuriganaTitle,
convertFuriganaTitleHtml
) where
import Hakyll (Item, Metadata, Compiler, itemIdentifier, getMetadata, lookupString)
import Debug.Trace (traceId)
import Data.Maybe (fromMaybe)
import Text.Regex.PCRE.Heavy
--------------------------------------------------------------------------------
-- FURIGANA CONVERSION
type FuriganaTemplate = String
convertTitle = updateFieldWith "title" "???"
convertFuriganaTitle :: Item a -> Compiler String
convertFuriganaTitle = convertTitle replaceFuriganaWithKanji
convertFuriganaTitleHtml :: Item a -> Compiler String
convertFuriganaTitleHtml = convertTitle replaceFuriganaWithHtml
updateFieldWith :: String -> String -> (String -> String) -> Item a -> Compiler String
updateFieldWith field defaultPreviousValue f =
fmap updateField . getMetadata . itemIdentifier
where
updateField :: Metadata -> String
updateField = traceId . f . fromMaybe defaultPreviousValue . lookupString field
replaceFuriganaWithKanji :: FuriganaTemplate -> String
replaceFuriganaWithKanji = gsub [re|\[(.*?)\]\((.*?)\)|] (\(kanji:kana:_) -> kanji :: String)
replaceFuriganaWithHtml :: FuriganaTemplate -> String
replaceFuriganaWithHtml = between "<ruby>" "</ruby>" . gsub [re|\[(.*?)\]\((.*?)\)|] (\(kanji:kana:_) -> "<rb>" ++ kanji ++"</rb> <rp>(</rp><rt> " ++ kana ++ "</rt><rp>)</rp>" :: String)
where
between x y s = x ++ s ++ y
-- toHtml :: FuriganaTemplate -> String
-- toHtml input =
-- "<ruby>"
-- <> subRegex (mkRegex "[(.*?)]\\((.*?)\\)") input "<rb>\1</rb> <rp>(</rp><rt>\2</rt><rp>)</rp>"
-- <> "</ruby>"
-- <!-- <ruby> -->
-- <!-- <rb>す</rb> <rp>(</rp><rt>為</rt><rp>)</rp> -->
-- <!-- <rb>る</rb> -->
-- <!-- </ruby> -->
-- <!-- " -->