]> Git — Sourcephile - sourcephile-web.git/blob - generator/Site/Render.hs
init
[sourcephile-web.git] / generator / Site / Render.hs
1 module Site.Render where
2
3 import Data.Map.Strict qualified as Map
4 import Data.Some (Some (..))
5 import Data.Text qualified as Text
6 import Ema qualified
7 import Ema.CLI qualified
8 import PyF
9 import Relude
10 import Text.Atom.Feed.Export qualified as Export (textFeed)
11 import Text.Blaze.Html.Renderer.Utf8 qualified as H
12 import Text.Blaze.Html5 ((!))
13 import Text.Blaze.Html5 qualified as H
14 import Text.Blaze.Html5.Attributes qualified as A
15 import Prelude ()
16
17 import Site.Body
18 import Site.Feed
19 import Site.Filter
20 import Site.Model
21 import Site.Page
22
23 renderRoute :: Some Ema.CLI.Action -> Model -> Route -> Ema.Asset LByteString
24 renderRoute emaAction model route = case route of
25 RoutePage pageName ->
26 Ema.AssetGenerated Ema.Html $
27 renderHtml $
28 case Map.lookup pageName (modelPosts model) of
29 Nothing -> error [fmt|Page not found in Model: {pageName:s}|]
30 Just page -> renderPage model (pageName, page)
31 RouteSpecial pageName ->
32 Ema.AssetGenerated Ema.Html $
33 renderHtml $
34 case Map.lookup pageName (modelSpecials model) of
35 Nothing -> error [fmt|Special Page not found in Model: {pageName:s}|]
36 Just page -> renderSpecial model page
37 RouteFeeds ->
38 Ema.AssetGenerated Ema.Html $
39 renderHtml
40 Content
41 { contentTitle = Just "Feeds"
42 , contentHtml = feedList model
43 }
44 RouteFilter filt ->
45 Ema.AssetGenerated Ema.Html $
46 renderHtml $
47 renderFilter model filt
48 RouteFilterAtom filt ->
49 Ema.AssetGenerated Ema.Other $
50 maybe (error "Feed malformed?") encodeUtf8 $
51 Export.textFeed $ mkFeed model filt
52 where
53 renderHtml content@Content{..} =
54 H.renderHtml do
55 H.docType
56 H.html ! A.lang "fr" $ do
57 H.head do
58 H.meta ! A.charset "UTF-8"
59 -- This makes the site mobile-friendly by default.
60 H.meta ! A.name "viewport" ! A.content "width=device-width, initial-scale=1"
61 -- When Ema.CLI.Generate this is https://unpkg.com/tailwindcss@2/dist/tailwind.css
62 -- When Ema.CLI.Run this is the output of windicss on the generated .html
63 H.link
64 ! A.rel "stylesheet"
65 ! A.type_ "text/css"
66 ! A.href "/static/css/windi.css"
67 when (Ema.CLI.isLiveServer emaAction) $
68 -- Add WindiCSS classes missing from https://unpkg.com/tailwindcss@2/dist/tailwind.css
69 H.link
70 ! A.rel "stylesheet"
71 ! A.type_ "text/css"
72 ! A.href "/static/css/windi-extras.css"
73 let localTitle = Text.intercalate " - " $ maybeToList contentTitle <> [orgName]
74 H.title $ H.text localTitle
75 --H.base ! A.href "/"
76 let description = "Some description."
77 H.meta ! A.name "description" ! A.content description
78 let openGraph (name :: Text) contentTag =
79 H.meta
80 ! H.customAttribute "property" [fmt|openGraph:{name}|]
81 ! A.content contentTag
82 openGraph "title" $ H.preEscapedTextValue localTitle
83 openGraph "description" description
84 openGraph "image" $ H.preEscapedTextValue $ absoluteLink model $ Left "static/img/image.jpg"
85 openGraph "image:alt" "some logo"
86 openGraph "locale" "fr_FR"
87 openGraph "type" "article"
88 openGraph "url" $ H.preEscapedTextValue $ absoluteLink model $ Left ""
89 -- H.link ! A.rel "icon" ! A.type_ "image/png" ! A.href "/static/img/favicon.png"
90 H.link
91 ! A.href "/static/css/extra.css"
92 ! A.rel "stylesheet"
93 ! A.type_ "text/css"
94 H.link
95 ! hrefRoute model (RouteFilterAtom $ Filter Nothing Nothing)
96 ! A.rel "alternate"
97 ! A.title [fmt|{orgName} - All Posts|]
98 ! A.type_ "application/atom+xml"
99 renderBody model route content