{-# LANGUAGE OverloadedStrings #-}
module Contexts.Core (
dateCtx
, jsPathCtx
, siteMapDateCtx
, siteCtx
) where
import Data.Functor ((<&>))
import Data.List.Extra (dropPrefix, mconcatMap)
import Data.String (fromString)
import qualified Data.Text.Lazy as TL
import Hakyll
import Lucid.Base (renderText)
import Lucid.Html5
import System.FilePath (takeDirectory, (</>))
import Config (contentsRoot, defaultTimeLocale',
siteName, timeZoneJST)
import qualified Config.Blogs.AnotherBlog as BA
import qualified Config.Blogs.TechBlog as TB
import Contexts.Field (localDateField)
dateCtx :: Context String
dateCtx :: Context String
dateCtx = TimeLocale -> TimeZone -> String -> String -> Context String
forall a. TimeLocale -> TimeZone -> String -> String -> Context a
localDateField TimeLocale
defaultTimeLocale' TimeZone
timeZoneJST String
"date" String
"%Y/%m/%d %R"
siteMapDateCtx :: Context String
siteMapDateCtx :: Context String
siteMapDateCtx = TimeLocale -> TimeZone -> String -> String -> Context String
forall a. TimeLocale -> TimeZone -> String -> String -> Context a
localDateField TimeLocale
defaultTimeLocale' TimeZone
timeZoneJST String
"date" String
"%Y-%m-%d"
techBlogCtx :: Context String
techBlogCtx :: Context String
techBlogCtx = ((String, String) -> Context String)
-> [(String, String)] -> Context String
forall b a. Monoid b => (a -> b) -> [a] -> b
mconcatMap ((String -> String -> Context String)
-> (String, String) -> Context String
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry String -> String -> Context String
forall a. String -> String -> Context a
constField) [
(String
"tech-blog-title", String
TB.blogName)
, (String
"tech-blog-description", String
TB.blogDesc)
, (String
"tech-blog-issue-req", String
"https://github.com/falgon/roki-web/issues/new/choose")
]
privBlogCtx :: Context String
privBlogCtx :: Context String
privBlogCtx = ((String, String) -> Context String)
-> [(String, String)] -> Context String
forall b a. Monoid b => (a -> b) -> [a] -> b
mconcatMap ((String -> String -> Context String)
-> (String, String) -> Context String
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry String -> String -> Context String
forall a. String -> String -> Context a
constField) [
(String
"diary-title", String
BA.blogName)
, (String
"diary-description", String
BA.blogDesc)
]
blogCtx :: Context String
blogCtx :: Context String
blogCtx = Context String
techBlogCtx Context String -> Context String -> Context String
forall a. Semigroup a => a -> a -> a
<> Context String
privBlogCtx
authorCtx :: Context String
authorCtx :: Context String
authorCtx = ((String, String) -> Context String)
-> [(String, String)] -> Context String
forall b a. Monoid b => (a -> b) -> [a] -> b
mconcatMap ((String -> String -> Context String)
-> (String, String) -> Context String
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry String -> String -> Context String
forall a. String -> String -> Context a
constField) [
(String
"author-name", String
"Roki")
, (String
"author-avator", String
"/images/avator/prof1000x1000.png")
, (String
"author-sex", String
"Male")
, (String
"author-locale", String
"Tokyo, JP")
, (String
"author-fav", String
fav)
, (String
"author-interested", String
"・FP ・Compiler ・Category theory ・Low layer networking, Infrastructure")
, (String
"author-job", String
"Software Engineer")
, (String
"author-github", String
"falgon")
, (String
"author-twitter", String
"roki_r7")
, (String
"author-note", String
"_roki")
, (String
"author-tumblr", String
"0x35")
, (String
"author-reddit", String
"r0k1")
, (String
"author-stackoverflow", String
"8345717")
, (String
"author-steam", String
"r0k1")
, (String
"author-yukicoder", String
"3223")
, (String
"author-teratail", String
"kjfkhfhgx")
, (String
"google-analytics", String
"UA-116653080-2")
]
where
fav :: String
fav = Text -> String
TL.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ HtmlT Identity () -> Text
forall a. Html a -> Text
renderText (HtmlT Identity () -> Text) -> HtmlT Identity () -> Text
forall a b. (a -> b) -> a -> b
$
[Attribute] -> HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
ul_ [Text -> Attribute
forall arg result. TermRaw arg result => arg -> result
style_ Text
"margin: 0;", Text -> Attribute
class_ Text
"comma-list"] (HtmlT Identity () -> HtmlT Identity ())
-> HtmlT Identity () -> HtmlT Identity ()
forall a b. (a -> b) -> a -> b
$ do
HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
li_ HtmlT Identity ()
"Coffee"
HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
li_ HtmlT Identity ()
"Watches"
HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
li_ (HtmlT Identity () -> HtmlT Identity ())
-> HtmlT Identity () -> HtmlT Identity ()
forall a b. (a -> b) -> a -> b
$ [Attribute] -> HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
a_
[Text -> Attribute
href_ Text
"https://www.san-x.co.jp/rilakkuma/profile/#&gid=1&pid=3"]
HtmlT Identity ()
"Kiiroitori"
HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
li_ (HtmlT Identity () -> HtmlT Identity ())
-> HtmlT Identity () -> HtmlT Identity ()
forall a b. (a -> b) -> a -> b
$ [Attribute] -> HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
a_
[Text -> Attribute
href_ Text
"disney_experience_summary/jp.html"]
HtmlT Identity ()
"Disney"
siteCtx :: Context String
siteCtx :: Context String
siteCtx = [Context String] -> Context String
forall a. Monoid a => [a] -> a
mconcat [
String -> String -> Context String
forall a. String -> String -> Context a
constField String
"lang" String
"ja"
, String -> String -> Context String
forall a. String -> String -> Context a
constField String
"site-title" String
siteName
, String -> String -> Context String
forall a. String -> String -> Context a
constField String
"site-description" String
"This is a Roki's website."
, String -> String -> Context String
forall a. String -> String -> Context a
constField String
"copyright" String
"copyright © 2016~ Roki All Rights Reserved."
, Context String
blogCtx
, Context String
authorCtx
]
jsPathCtx :: Context String
jsPathCtx :: Context String
jsPathCtx = String
-> Context String
-> (Item String -> Compiler [Item String])
-> Context String
forall a b.
String -> Context a -> (Item b -> Compiler [Item a]) -> Context b
listFieldWith String
"js" Context String
ctx ((Item String -> Compiler [Item String]) -> Context String)
-> (Item String -> Compiler [Item String]) -> Context String
forall a b. (a -> b) -> a -> b
$ \Item String
item ->
Identifier -> String -> Compiler (Maybe String)
forall (m :: * -> *).
MonadMetadata m =>
Identifier -> String -> m (Maybe String)
getMetadataField (Item String -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item String
item) String
"js" Compiler (Maybe String)
-> (Maybe String -> [Item String]) -> Compiler [Item String]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
[Item String]
-> (String -> [Item String]) -> Maybe String -> [Item String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Item String]
forall a. Monoid a => a
mempty ((String -> Item String) -> [String] -> [Item String]
forall a b. (a -> b) -> [a] -> [b]
map (Item String -> String -> Item String
forall {a}. Item a -> String -> Item String
itemize Item String
item (String -> Item String)
-> (String -> String) -> String -> Item String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
trim) ([String] -> [Item String])
-> (String -> [String]) -> String -> [Item String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [String]
splitAll String
",")
where
ctx :: Context String
ctx = String -> (Item String -> Compiler String) -> Context String
forall a. String -> (Item a -> Compiler String) -> Context a
field String
"src-script" (String -> Compiler String
forall a. a -> Compiler a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Compiler String)
-> (Item String -> String) -> Item String -> Compiler String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item String -> String
forall a. Item a -> a
itemBody)
itemize :: Item a -> String -> Item String
itemize Item a
item String
md = Item {
itemIdentifier :: Identifier
itemIdentifier = String -> Identifier
forall a. IsString a => String -> a
fromString String
md
, itemBody :: String
itemBody = Item a -> String
forall {a}. Item a -> String
jsDirPath Item a
item String -> String -> String
</> String
md
}
jsDirPath :: Item a -> String
jsDirPath = String -> String -> String
forall a. Eq a => [a] -> [a] -> [a]
dropPrefix String
contentsRoot
(String -> String) -> (Item a -> String) -> Item a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
takeDirectory
(String -> String) -> (Item a -> String) -> Item a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identifier -> String
toFilePath
(Identifier -> String)
-> (Item a -> Identifier) -> Item a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item a -> Identifier
forall a. Item a -> Identifier
itemIdentifier