Rename 成り立ち to 語源, and fix index titles
This commit is contained in:
parent
0fc37f3167
commit
ec31242981
|
@ -1,6 +1,6 @@
|
||||||
---
|
---
|
||||||
desc: "I announce myself to the world"
|
desc: "I announce myself to the world"
|
||||||
keywords: "japanese, naritachi, grammar"
|
keywords: "japanese, gogen, grammar"
|
||||||
lang: "en"
|
lang: "en"
|
||||||
updated: "2020-09-22T12:00:00Z"
|
updated: "2020-09-22T12:00:00Z"
|
||||||
title: "[為](す)る"
|
title: "[為](す)る"
|
|
@ -31,9 +31,9 @@ title: "Nani"
|
||||||
<div class="pure-u-1-2 pure-u-md-1-2">
|
<div class="pure-u-1-2 pure-u-md-1-2">
|
||||||
<h2>語源</h2>
|
<h2>語源</h2>
|
||||||
<ul>
|
<ul>
|
||||||
$for(naritachi)$
|
$for(gogen)$
|
||||||
<li>
|
<li>
|
||||||
<div><a href=".$url$">$title$</a></div>
|
<div><a href=".$url$">$titleHtml$</a></div>
|
||||||
</li>
|
</li>
|
||||||
$endfor$
|
$endfor$
|
||||||
</ul>
|
</ul>
|
||||||
|
|
|
@ -1,14 +1,15 @@
|
||||||
{-# LANGUAGE QuasiQuotes, FlexibleContexts #-}
|
{-# LANGUAGE QuasiQuotes, FlexibleContexts #-}
|
||||||
|
|
||||||
module Formats.Naritachi (
|
module Formats.Gogen (
|
||||||
convertFuriganaTitle,
|
convertFuriganaTitle,
|
||||||
convertFuriganaTitleHtml
|
convertFuriganaTitleHtml,
|
||||||
|
gogenCtx,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Hakyll (Item, Metadata, Compiler, itemIdentifier, getMetadata, lookupString)
|
import Hakyll
|
||||||
import Debug.Trace (traceId)
|
import Debug.Trace (traceId)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Text.Regex.PCRE.Heavy
|
import Text.Regex.PCRE.Heavy (gsub, re)
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
-- FURIGANA CONVERSION
|
-- FURIGANA CONVERSION
|
||||||
|
@ -37,15 +38,10 @@ replaceFuriganaWithHtml :: FuriganaTemplate -> String
|
||||||
replaceFuriganaWithHtml = between "<ruby>" "</ruby>" . gsub [re|\[(.*?)\]\((.*?)\)|] (\(kanji:kana:_) -> "<rb>" ++ kanji ++"</rb> <rp>(</rp><rt> " ++ kana ++ "</rt><rp>)</rp>" :: String)
|
replaceFuriganaWithHtml = between "<ruby>" "</ruby>" . gsub [re|\[(.*?)\]\((.*?)\)|] (\(kanji:kana:_) -> "<rb>" ++ kanji ++"</rb> <rp>(</rp><rt> " ++ kana ++ "</rt><rp>)</rp>" :: String)
|
||||||
where
|
where
|
||||||
between x y s = x ++ s ++ y
|
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> -->
|
gogenCtx :: Context String
|
||||||
-- <!-- <rb>す</rb> <rp>(</rp><rt>為</rt><rp>)</rp> -->
|
gogenCtx =
|
||||||
-- <!-- <rb>る</rb> -->
|
dateField "date" "%Y-%m-%d"
|
||||||
-- <!-- </ruby> -->
|
<> field "titleHtml" convertFuriganaTitleHtml
|
||||||
-- <!-- " -->
|
<> defaultContext
|
||||||
|
|
|
@ -19,7 +19,7 @@ import Text.Pandoc.Highlighting (Style, breezeDark, styleToCss)
|
||||||
|
|
||||||
-- ---------
|
-- ---------
|
||||||
|
|
||||||
import Formats.Naritachi
|
import Formats.Gogen
|
||||||
import Util.Routes
|
import Util.Routes
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
@ -73,14 +73,14 @@ main = hakyllWith config $ do
|
||||||
match "posts/*" $ do
|
match "posts/*" $ do
|
||||||
let ctx = constField "type" "article" <> postCtx
|
let ctx = constField "type" "article" <> postCtx
|
||||||
|
|
||||||
route $ metadataRoute titleRoute `composeRoutes` (prefixRoute "posts/")
|
route $ metadataRoute titleRoute `composeRoutes` prefixRoute "posts/"
|
||||||
compile $
|
compile $
|
||||||
pandocCompilerCustom
|
pandocCompilerCustom
|
||||||
>>= loadAndApplyTemplate "templates/post.html" ctx
|
>>= loadAndApplyTemplate "templates/post.html" ctx
|
||||||
>>= saveSnapshot "content"
|
>>= saveSnapshot "content"
|
||||||
>>= loadAndApplyTemplate "templates/default.html" ctx
|
>>= loadAndApplyTemplate "templates/default.html" ctx
|
||||||
|
|
||||||
match "naritachi/*" $ do
|
match "gogen/*" $ do
|
||||||
let ctx =
|
let ctx =
|
||||||
constField "type" "article"
|
constField "type" "article"
|
||||||
<> field "title" convertFuriganaTitle
|
<> field "title" convertFuriganaTitle
|
||||||
|
@ -91,7 +91,7 @@ main = hakyllWith config $ do
|
||||||
compile $ do
|
compile $ do
|
||||||
|
|
||||||
pandocCompilerCustom
|
pandocCompilerCustom
|
||||||
>>= loadAndApplyTemplate "templates/naritachi.html" ctx
|
>>= loadAndApplyTemplate "templates/gogen.html" ctx
|
||||||
>>= saveSnapshot "content"
|
>>= saveSnapshot "content"
|
||||||
>>= loadAndApplyTemplate "templates/default.html" ctx
|
>>= loadAndApplyTemplate "templates/default.html" ctx
|
||||||
|
|
||||||
|
@ -100,11 +100,11 @@ main = hakyllWith config $ do
|
||||||
compile $ do
|
compile $ do
|
||||||
-- posts :: Compiler
|
-- posts :: Compiler
|
||||||
posts <- recentFirst =<< loadAll "posts/*"
|
posts <- recentFirst =<< loadAll "posts/*"
|
||||||
naritachi <- loadAll "naritachi/*"
|
gogen <- loadAll "gogen/*"
|
||||||
|
|
||||||
let indexCtx =
|
let indexCtx =
|
||||||
listField "posts" postCtx (return posts)
|
listField "posts" postCtx (return posts)
|
||||||
<> listField "naritachi" postCtx (return naritachi)
|
<> listField "gogen" gogenCtx (return gogen)
|
||||||
<> constField "root" root
|
<> constField "root" root
|
||||||
<> constField "siteName" siteName
|
<> constField "siteName" siteName
|
||||||
<> defaultContext
|
<> defaultContext
|
||||||
|
|
Loading…
Reference in New Issue