acatalepsie/src/Templates.hs

144 lines
5.4 KiB
Haskell
Raw Normal View History

2020-07-12 02:18:11 +00:00
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE DisambiguateRecordFields #-}
2020-09-26 23:33:50 +00:00
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
2020-07-12 02:18:11 +00:00
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
2020-06-13 16:22:47 +00:00
module Templates where
2020-09-26 21:21:49 +00:00
import Data.Time (UTCTime)
2020-09-25 23:45:58 +00:00
import Data.Time.Format (formatTime, defaultTimeLocale)
import Data.Time.LocalTime (zonedTimeToUTC)
2020-09-26 23:33:50 +00:00
import qualified Data.Map.Strict as Map
import Achille.Internal.IO (AchilleIO)
import Achille.Writable as Writable
import Lucid
import Lucid.Base (makeAttribute)
2020-06-13 16:22:47 +00:00
2020-07-12 02:18:11 +00:00
import Types
2020-09-25 23:45:58 +00:00
import Common
import Config
2020-09-26 23:33:50 +00:00
instance AchilleIO m => Writable m (Html a) where
write to = Writable.write to . renderBS
2020-06-13 16:22:47 +00:00
2020-09-26 21:21:49 +00:00
showDate :: UTCTime -> String
showDate = formatTime defaultTimeLocale "%b %d, %_Y"
2020-06-13 16:22:47 +00:00
2020-09-26 23:33:50 +00:00
loading_ :: Text -> Attribute
loading_ = makeAttribute "loading"
2020-06-13 16:22:47 +00:00
2020-09-26 23:33:50 +00:00
property_ :: Text -> Attribute
property_ = makeAttribute "property"
2020-07-12 02:18:11 +00:00
2020-09-26 23:33:50 +00:00
toLink :: FilePath -> Html () -> Html ()
toLink url = a_ [ href_ (fromString $ "/" <> url) ]
2020-06-13 16:22:47 +00:00
2020-09-26 23:33:50 +00:00
renderProject :: Project -> [(String, FilePath)] -> Text -> Html ()
2020-07-12 02:18:11 +00:00
renderProject (project@Project{title,..}) children content =
2020-09-25 23:45:58 +00:00
outerWith def { Config.title = fromString title
, Config.description = fromString subtitle
} do
2020-09-26 23:33:50 +00:00
header_ [ class_ "project" ] do
div_ (img_ [ src_ "logo.svg" ])
div_ do
h1_ (fromString title)
p_ (fromString subtitle)
ul_ $ forM_ (Map.toList labels) \(k, v) -> li_ do
2020-06-13 16:22:47 +00:00
fromString k <> ": "
if k == "repo" then
2020-09-26 23:33:50 +00:00
a_ [ href_ (fromString $ "https://github.com/" <> v) ]
2020-06-13 16:22:47 +00:00
$ fromString v
else fromString v
2020-07-12 02:18:11 +00:00
when (length children > 0) $
2020-09-26 23:33:50 +00:00
ol_ [ class_ "pages" ] $ forM_ children \(t,l) ->
li_ $ a_ [ href_ (fromString l) ] (fromString t)
toHtmlRaw content
2020-06-13 16:22:47 +00:00
2020-09-26 23:33:50 +00:00
renderReadings :: [Book] -> Html ()
2020-09-25 23:45:58 +00:00
renderReadings books =
outerWith def { Config.title = "readings"
, Config.description = "books I've read"
} do
2020-09-26 23:33:50 +00:00
table_ [ class_ "books" ] $
2020-09-25 23:45:58 +00:00
forM_ books \ Book {title,author,rating,completed} ->
2020-09-26 23:33:50 +00:00
tr_ do
td_ (toHtml title)
td_ (toHtml author)
td_ $ fromString $ case rating of
2020-09-25 23:45:58 +00:00
Just r -> replicate r '★'
Nothing -> "·"
2020-09-26 23:33:50 +00:00
td_ $ fromString $ case completed of
2020-09-25 23:45:58 +00:00
Just d -> formatTime defaultTimeLocale "%m/%0Y"
$ zonedTimeToUTC d
Nothing -> "·"
2020-09-26 23:33:50 +00:00
renderProjects :: Text -> [(Project, FilePath)] -> Html ()
2020-06-13 16:22:47 +00:00
renderProjects txt paths =
outer do
2020-09-26 23:33:50 +00:00
toHtmlRaw txt
ul_ [ class_ "projects" ] do
forM_ paths \(Project {title,..}, link) -> li_ $ a_ [ href_ (fromString link) ] $ do
div_ $ img_ [ src_ (fromString $ link </> "logo.svg") ]
div_ do
h2_ (fromString title)
p_ (fromString subtitle)
2020-06-13 16:22:47 +00:00
-- H.ul $ forM_ (Map.toList $ Types.labels project) \(k, v) ->
-- H.li $ (fromString k <> ": " <> fromString v)
2020-09-26 23:33:50 +00:00
logo :: Html ()
logo = toHtmlRaw ("<svg xmlns=\"http://www.w3.org/2000/svg\" version=\"1.1\" height=\"19px\" width=\"29px\"><path d=\"M 2,2 A 5,5 0 0 1 7,7 L 7, 12 A 5, 5 0 0 1 2,17 M 7,7 A 5,5 0 0 1 12,2 L 22,2 A 5,5 0 0 1 27,7 L 27,12 A 5, 5 0 0 1 22,17 L 12,17\" style=\"stroke-width: 2; stroke-linecap: butt; stroke-linejoin: bevel; stroke: #fff\" fill=\"none\"/></svg>" :: Text)
2020-06-13 16:22:47 +00:00
2020-09-26 23:33:50 +00:00
outer :: Html () -> Html ()
2020-07-12 02:18:11 +00:00
outer = outerWith def
2020-09-26 23:33:50 +00:00
outerWith :: SiteConfig -> Html () -> Html ()
outerWith SiteConfig{title,..} content = doctypehtml_ do
head_ do
meta_ [ name_ "viewport"
, content_ "width=device-width, initial-scale=1.0, user-scalable=yes"
]
meta_ [ name_ "theme-color", content_ "#000000" ]
meta_ [ name_ "robots", content_ "index, follow" ]
meta_ [ charset_ "utf-8" ]
link_ [ rel_ "stylesheet", href_ "/assets/theme.css" ]
link_ [ rel_ "shortcut icon"
, type_ "image/svg"
, href_ "/assets/favicon.svg"
]
link_ [ rel_ "alternate"
, type_ "application/atom+xml"
, href_ "/atom.xml"
]
meta_ [ property_ "og:title", content_ title ]
meta_ [ property_ "og:type", content_ "website" ]
meta_ [ property_ "og:image", content_ image ]
meta_ [ property_ "og:description", content_ description ]
title_ $ toHtml title
body_ do
header_ [ id_ "hd" ] $ section_ do
a_ [ href_ "/" ] $ logo
section_ $ nav_ do
a_ [ href_ "/projects.html" ] "Projects"
a_ [ href_ "/visual.html" ] "Visual"
a_ [ href_ "/readings.html" ] "Readings"
a_ [ href_ "/quid.html" ] "Quid"
a_ [ href_ "/atom.xml" ] "Feed"
main_ content
footer_ [ id_ "ft" ] do
2020-06-13 16:22:47 +00:00
"flupe 2020 · "
2020-09-26 23:33:50 +00:00
a_ [ href_ "https://creativecommons.org/licenses/by-nc/2.0/" ]
"CC BY-NC 2.0"
2020-06-13 16:22:47 +00:00
" · "
2020-09-26 23:33:50 +00:00
a_ [ href_ "https://instagram.com/ba.bou.m/" ] "instagram"
2020-09-26 21:21:49 +00:00
" · "
2020-09-26 23:33:50 +00:00
a_ [ href_ "/atom.xml" ] "feed"