{-# LANGUAGE OverloadedStrings #-}
module Config.Blogs.AnotherBlog (
    blogName
  , blogDesc
  , entryPattern
  , entryFilesPattern
  , feedConfig
  , contentSnapshot
  , tagPagesPath
  , buildTags
  , yearlyPagePath
  , buildYearlyArchives
  , monthlyPagePath
  , buildMonthlyArchives
) where

import           Data.String           (fromString)
import qualified Data.Text             as T
import qualified Data.Text.Lazy        as TL
import qualified Hakyll                as H
import           Hakyll.Web.Feed.Extra hiding (renderAtom)
import           Lucid.Base            (renderText)
import           Lucid.Html5

import qualified Archives              as A
import qualified Config.Blogs.Utils    as BU
import           Config.Site           (siteName)

{-# INLINE blogName #-}
blogName :: FilePath
blogName :: String
blogName = String
"roki.diary"

blogDesc :: String
blogDesc :: String
blogDesc = 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
$ do
    [Attribute] -> HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
a_ [Text -> Attribute
href_ (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"/" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
blogName] (HtmlT Identity () -> HtmlT Identity ())
-> HtmlT Identity () -> HtmlT Identity ()
forall a b. (a -> b) -> a -> b
$ String -> HtmlT Identity ()
forall a. IsString a => String -> a
fromString String
blogName
    [Attribute] -> HtmlT Identity () -> HtmlT Identity ()
forall arg result. Term arg result => arg -> result
p_ [Text -> Attribute
class_ Text
"is-inline"] (HtmlT Identity () -> HtmlT Identity ())
-> HtmlT Identity () -> HtmlT Identity ()
forall a b. (a -> b) -> a -> b
$
        HtmlT Identity ()
" is just a diary. I write about my daily events and thoughts "
            HtmlT Identity () -> HtmlT Identity () -> HtmlT Identity ()
forall a. Semigroup a => a -> a -> a
<> HtmlT Identity ()
"(Most of the content of the article is written in Japanese)."

-- contents/roki.log/year/month/day/title/index.md
entryPattern :: H.Pattern
entryPattern :: Pattern
entryPattern = String -> Pattern
BU.entryPattern String
blogName

entryFilesPattern :: H.Pattern
entryFilesPattern :: Pattern
entryFilesPattern = String -> Pattern
BU.entryFilesPattern String
blogName

feedConfig :: FeedConfiguration
feedConfig :: FeedConfiguration
feedConfig = FeedConfiguration {
    feedTitle :: String
feedTitle = String
blogName
  , feedWebRoot :: String
feedWebRoot = String
"https://" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
siteName
  , feedBlogName :: String
feedBlogName = String
blogName
  , feedDescription :: String
feedDescription = String
"Roki Diary"
  , feedAuthorName :: String
feedAuthorName = String
"Roki"
  , feedAuthorEmail :: String
feedAuthorEmail = String
"falgon53@yahoo.co.jp"
  }

{-# INLINE contentSnapshot #-}
contentSnapshot :: H.Snapshot
contentSnapshot :: String
contentSnapshot = String -> String
BU.contentSnapshot String
blogName

tagPagesPath :: FilePath -> FilePath
tagPagesPath :: String -> String
tagPagesPath = String -> String -> String
BU.tagPagesPath String
blogName

buildTags :: H.MonadMetadata m => m H.Tags
buildTags :: forall (m :: * -> *). MonadMetadata m => m Tags
buildTags = String -> m Tags
forall (m :: * -> *). MonadMetadata m => String -> m Tags
BU.buildTags String
blogName

{-# INLINE yearlyPagePath #-}
yearlyPagePath :: FilePath -> FilePath
yearlyPagePath :: String -> String
yearlyPagePath = String -> String -> String
BU.yearlyPagePath String
blogName

buildYearlyArchives :: (H.MonadMetadata m, MonadFail m) => m A.YearlyArchives
buildYearlyArchives :: forall (m :: * -> *).
(MonadMetadata m, MonadFail m) =>
m YearlyArchives
buildYearlyArchives = String -> m YearlyArchives
forall (m :: * -> *).
(MonadMetadata m, MonadFail m) =>
String -> m YearlyArchives
BU.buildYearlyArchives String
blogName

{-# INLINE monthlyPagePath #-}
monthlyPagePath :: (FilePath, FilePath) -> FilePath
monthlyPagePath :: (String, String) -> String
monthlyPagePath = String -> (String, String) -> String
BU.monthlyPagePath String
blogName

buildMonthlyArchives :: (H.MonadMetadata m, MonadFail m) => m A.MonthlyArchives
buildMonthlyArchives :: forall (m :: * -> *).
(MonadMetadata m, MonadFail m) =>
m MonthlyArchives
buildMonthlyArchives = String -> m MonthlyArchives
forall (m :: * -> *).
(MonadMetadata m, MonadFail m) =>
String -> m MonthlyArchives
BU.buildMonthlyArchives String
blogName