~alcinnz/amphiarao

ref: 7a6334be0be533bcd94be41d2542483c81a08bc1 amphiarao/src/UI/Templates.hs -rw-r--r-- 2.2 KiB
7a6334be — Adrian Cochrane Allow testing reloading of webpages. 3 years ago
                                                                                
d4c10f89 Adrian Cochrane
8a39949f Adrian Cochrane
d4c10f89 Adrian Cochrane
7a6334be Adrian Cochrane
8a39949f Adrian Cochrane
d4c10f89 Adrian Cochrane
8a39949f Adrian Cochrane
d4c10f89 Adrian Cochrane
8a39949f Adrian Cochrane
d4c10f89 Adrian Cochrane
8a39949f Adrian Cochrane
d4c10f89 Adrian Cochrane
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
module UI.Templates(page, inspector, sessionForm) where

import Happstack.Lite
import Text.Blaze.Html5 as H
import Text.Blaze.Html5.Attributes as A
import Text.Blaze.Html
import Data.Text as Txt

import Internal
import Control.Monad.IO.Class (liftIO)
import Control.Concurrent.MVar
import Data.UUID as ID

import Messages
import Happstack.Server.I18N

page :: (Response -> ServerPart Response) -> [Text] -> ([Text] -> Html) -> ServerPart Response
page return' title body' = do
    langs <- bestLanguage <$> acceptLanguage
    return' $ toResponse $ html $ do
        H.head $ do
            H.title $ text $ intercalate " — " title
        body $ body' langs

inspector :: (Response -> ServerPart Response) -> Text -> Session' -> ([Text] -> Html) -> ServerPart Response
inspector return' title session' body' = do
    let uuid' = ID.toString $ uuid_ session'
    let timeout = H.stringValue $ show $ pageLoad $ timeouts session'
    page return' [title, pack $ show $ currentURL $ session', "Amphiarao"] $ \langs -> do
        header $ do
            H.form ! action' ["/", uuid', "/nav/reload"] ! alt (l' langs Reload') ! A.method "POST" $ do
                button ! type_ "submit" ! A.title (l' langs Reload') $ "↻"
            H.form ! action' ["/", uuid', "/search"] ! alt (l' langs Search') $ do
                input ! type_ "search" ! name "q" ! placeholder (l' langs Search')
        body' langs
        footer $ do
            H.form ! action' ["/close/", uuid'] ! A.method "POST" ! alt (l' langs CloseSession') $ do
                button ! type_ "submit" $ l langs CloseSession
            hr
            H.form ! action' ["/", uuid', "/timeout"] ! A.method "POST" ! alt (l' langs LoadTimeout') $ p $ do
                H.label $ do
                    l langs LoadTimeout
                    input ! type_ "number" ! name "pageLoad" ! value timeout
                text "ms"

  where
    action' = A.action . H.stringValue . Prelude.concat

sessionForm langs = H.form ! A.method "POST" ! action "/" ! alt (l' langs CreateSession') $ do
    input ! type_ "url" ! name "target" ! placeholder "URL to debug"
    button ! type_ "submit" $ l langs CreateSession