gdritter repos new-inf-blog / d53b307
Start doing OpenGraph preview stuff Getty Ritter 4 years ago
4 changed file(s) with 84 addition(s) and 39 deletion(s). Collapse all Expand all
11 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE NamedFieldPuns #-}
23
34 module Inf.Templates
45 ( main
89 , edit
910 , post
1011 , delete
12 , Main(..)
1113
1214 , dbException
1315 , someException
1820 ) where
1921
2022 import qualified Control.Exception as Exn
21 import Control.Monad ((=<<))
2223 import Data.Aeson ((.=))
2324 import qualified Data.Aeson as Aeson
2425 import Data.Monoid ((<>))
4748 loggedError = show
4849
4950 instance InternalError Unimplemented where
50 renderedError (Unimplemented _) =
51 main Nothing "Unimplemented" =<<
52 page "IMPLEMENT ME"
51 renderedError (Unimplemented _) = main Main
52 { mainUser = Nothing
53 , mainTitle = "Unimplemented"
54 , mainContents = "IMPLEMENT ME"
55 , mainUrl = "/"
56 }
5357
5458 loggedError (Unimplemented msg) = "Unimplemented: " ++ msg
5559
6872 pandoc <- Pandoc.readMarkdown markdownOpts raw
6973 Pandoc.writeHtml5String htmlOpts pandoc
7074
71 main :: Maybe TS.Text -> T.Text -> T.Text -> IO T.Text
72 main user title contents = do
75 data Main = Main
76 { mainUser :: !(Maybe TS.Text)
77 , mainTitle :: !T.Text
78 , mainContents :: !T.Text
79 , mainUrl :: !TS.Text
80 }
81
82 main :: Main -> IO T.Text
83 main Main { mainUser, mainTitle, mainContents, mainUrl } = do
7384 template <- Stache.compileMustacheFile "templates/main.mustache"
7485 let vals = Aeson.object
75 [ "title" .= title
76 , "contents" .= contents
77 , "user" .= case user of
86 [ "title" .= mainTitle
87 , "contents" .= mainContents
88 , "user" .= case mainUser of
7889 Nothing -> Aeson.toJSON ()
7990 Just u -> Aeson.object [ "name" .= u ]
91 , "url" .= mainUrl
8092 ]
8193 pure (Stache.renderMustache template vals)
8294
150162
151163
152164 dbException :: DBException -> IO T.Text
153 dbException exn = main Nothing "Error" =<< page (TS.unlines
154 ( "## Internal server error"
155 : case exn of
156 NoSuchPost -> [ "database misconfiguration" ]
157 BadUserError -> [ "bad user session" ]
158 NonUniqueResult -> [ "database misconfiguration" ]
159 MissingPost pId -> [ "missing post: `" <> TS.pack (show pId) <> "`"]
160 MissingPage name -> [ "missing page: `" <> name <> "`"]
161 NoPostFound year month slug ->
162 [ "no such post: `" <> year <> "/" <> month <> "/" <> slug <> "`" ]
163 ))
165 dbException exn = do
166 contents <- page $ TS.unlines
167 ( "## Internal server error"
168 : case exn of
169 NoSuchPost -> [ "database misconfiguration" ]
170 BadUserError -> [ "bad user session" ]
171 NonUniqueResult -> [ "database misconfiguration" ]
172 MissingPost pId -> [ "missing post: `" <> TS.pack (show pId) <> "`"]
173 MissingPage name -> [ "missing page: `" <> name <> "`"]
174 NoPostFound year month slug ->
175 [ "no such post: `" <> year <> "/" <> month <> "/" <> slug <> "`" ]
176 )
177 main Main
178 { mainUser = Nothing
179 , mainTitle = "Error"
180 , mainContents = contents
181 , mainUrl = "/"
182 }
164183
165184 someException :: Exn.SomeException -> IO T.Text
166 someException exn = main Nothing "Internal Sever Error" =<< page (TS.unlines
167 [ "The following unexpected error occurred:"
168 , "```"
169 , TS.pack (show exn)
170 , "```"
171 ])
185 someException exn = do
186 contents <- page $ TS.unlines
187 [ "The following unexpected error occurred:"
188 , "```"
189 , TS.pack (show exn)
190 , "```"
191 ]
192 main Main
193 { mainUser = Nothing
194 , mainTitle = "Internal Server Error"
195 , mainContents = contents
196 , mainUrl = "/"
197 }
6565 `Exn.catch` (\ (e :: Exn.SomeException) -> raise500 r e)
6666 k resp
6767
68 ok :: Maybe TS.Text -> T.Text -> T.Text -> IO W.Response
69 ok user title stuff = do
70 pg <- Template.main user title stuff
68 ok :: Maybe TS.Text -> T.Text -> T.Text -> TS.Text -> IO W.Response
69 ok user title stuff url = do
70 pg <- Template.main Template.Main
71 { Template.mainUser = user
72 , Template.mainTitle = title
73 , Template.mainContents = stuff
74 , Template.mainUrl = url
75 }
7176 let headers = [(HTTP.hContentType, "text/html")]
7277 pure (W.responseLBS HTTP.status200 headers (Encoding.encodeUtf8 pg))
7378
8085 [ "No handler found for page "
8186 , "`/" <> TS.intercalate "/" msgs <> "`"
8287 ]
83 pg <- Template.main Nothing "404" contents
88 pg <- Template.main Template.Main
89 { Template.mainUser = Nothing
90 , Template.mainTitle ="404"
91 , Template.mainContents = contents
92 , Template.mainUrl = "/"
93 }
8494 pure (W.responseLBS HTTP.status404 [] (Encoding.encodeUtf8 pg))
8595
8696 raise500 :: Template.InternalError e => W.Request -> e -> IO W.Response
5656
5757 ("GET", ["auth"]) -> do
5858 password <- Template.login
59 Web.ok user "login" password
59 Web.ok user "login" password "/"
6060
6161 ("GET", ["archive"]) -> do
6262 posts <- DB.runDB c DB.allPostRefs
6363 contents <- Template.list posts
64 Web.ok user "Past Entries" contents
64 Web.ok user "Past Entries" contents "/archive"
6565
6666 ("GET", ["create"]) ->
6767 case user of
6868 Nothing -> Web.redirect "/"
6969 Just _ -> do
7070 contents <- Template.edit "/" emptyRawPost
71 Web.ok user "New Post" contents
71 Web.ok user "New Post" contents "/"
7272
7373 ("GET", [y, m, s]) -> do
7474 (post, cached) <- DB.runDB c $ do
7777 pure (ps, ch)
7878 case cached of
7979 Just cache -> do
80 Web.ok user (T.fromStrict (postTitle post)) cache
80 Web.ok user (T.fromStrict (postTitle post)) cache (postURL post)
8181 Nothing -> do
8282 contents <- Template.post user post
8383 DB.runDB c (DB.storeCachedMarkup (postId post) contents)
84 Web.ok user (T.fromStrict (postTitle post)) contents
84 Web.ok user (T.fromStrict (postTitle post)) contents (postURL post)
8585
8686 ("POST", [y, m, s]) ->
8787 case user of
116116 Just {} -> do
117117 oldPost <- DB.runDB c (DB.postByDateAndSlug y m s)
118118 contents <- Template.edit (postURL oldPost) (postToRawPost oldPost)
119 Web.ok user (T.fromStrict (postTitle oldPost)) contents
119 Web.ok user (T.fromStrict (postTitle oldPost)) contents "/"
120120
121121 ("POST", [y, m, s, "delete"]) ->
122122 case user of
134134 Just _ -> do
135135 post <- DB.runDB c (DB.postByDateAndSlug y m s)
136136 contents <- Template.delete post
137 Web.ok user "Delete Post?" contents
137 Web.ok user "Delete Post?" contents "/"
138138
139139 ("POST", ["login"]) -> do
140140 formData <- Web.formData req
181181 ("GET", [pagename]) -> do
182182 pg <- DB.runDB c (DB.staticPage pagename)
183183 contents <- Template.page (pageText pg)
184 Web.ok user (T.fromStrict pagename) contents
184 Web.ok user (T.fromStrict pagename) contents ("/" <> pagename)
185185
186186 ("GET", [_page, "edit"]) ->
187187 case user of
188188 Nothing -> Web.redirect "/"
189189 Just _ -> do
190190 contents <- Template.edit "/" emptyRawPost
191 Web.ok user "New Post" contents
191 Web.ok user "New Post" contents "/"
192192
193193 (_, path) -> Web.raise404 req path
99 <link rel="alternate" type="application/rss+xml"
1010 title="Infinite Negative Utility"
1111 href="/rss" />
12
13 <meta property="og:title" content=""/>
14 <meta property="og:url" content="{{url}}"/>
15 <meta property="og:image" content="/static/inf-icon-128x128.png"/>
16 <meta property="og:type" content="website"/>
17 <meta property="og:description" content="{{title}}"/>
18 <meta property="og:image:width" content="128"/>
19 <meta property="og:image:height" content="128"/>
20 <meta property="og:site_name" content="Infinite Negative Utility"/>
1221 <title>{{title}} — Infinite Negative Utility</title>
1322 </head>
1423 <body>