~alcinnz/amphiarao

ref: d4c10f895dce29c0eb5b6209fb228abc731e7b5a amphiarao/src/Main.hs -rw-r--r-- 3.9 KiB
d4c10f89 — Adrian Cochrane Allow loading webpage, commit missing files. 3 years ago
                                                                                
505d1225 Adrian Cochrane
d4c10f89 Adrian Cochrane
505d1225 Adrian Cochrane
d4c10f89 Adrian Cochrane
505d1225 Adrian Cochrane
d4c10f89 Adrian Cochrane
505d1225 Adrian Cochrane
d4c10f89 Adrian Cochrane
505d1225 Adrian Cochrane
d4c10f89 Adrian Cochrane
505d1225 Adrian Cochrane
d4c10f89 Adrian Cochrane
505d1225 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
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
module Main where

import Happstack.Lite
import Happstack.Server.RqData
import Control.Concurrent.MVar
import Data.HashMap.Strict as M

import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
import Text.Blaze.Html (text, string)
import qualified Data.Text as Txt

import Webdriver
import Data.UUID as ID

import Messages
import Happstack.Server.I18N

import Internal
import Internal.Load as Load
import Control.Monad.IO.Class (liftIO)
import Control.Monad (forM)

import qualified UI.Templates as Tpl
import qualified UI.Search as Q

main :: IO ()
main = do
  sessions <- initSessions
  serve Nothing $ msum [
      dir "webdriver" $ dir "v1" $ serveWebdriver sessions,
      postHome sessions,
      serveHome,
      dir "preview-prompt" servePreviewPrompt,
      dir "close" $ path $ deleteSession sessions,
      path $ serveSession sessions
    ]

serveHome :: ServerPart Response
serveHome = do
    nullDir
    method GET
    Tpl.page ok ["Amphiarao"] $ \langs -> do
        l langs AmphiaraoIntro
        Tpl.sessionForm langs

postHome sessions = do
    nullDir
    method POST
    (uuid, session) <- liftIO $ createSession sessions M.empty
    target <- looks "target"
    -- Not much point of a blank session, so allow loading here.
    case target of
        (target':_) | Just url <- Load.parseAbsoluteURI target' -> liftIO $ Load.load session url
        _ -> return ()
    seeOther ('/' : ID.toString uuid) $ toResponse ()

deleteSession sessions uuid = do
    nullDir
    method POST
    case ID.fromString uuid of
        Just id -> liftIO $ delSession id sessions
        Nothing -> return ()
    seeOther ['/'] $ toResponse ()

servePreviewPrompt = do
    nullDir
    method GET
    Tpl.page ok ["?", "Amphiarao"] $ \langs -> H.p $ l langs PromptPreview

serveSession :: Sessions -> String -> ServerPart Response
serveSession = withSession session404 $ \uuid session -> msum [
        sessionHome uuid session,
        dir "timeout" $ setTimeout uuid session,
        dir "search" $ searchSession uuid session,
        dir "nav" $ msum [
            dir "load" $ loadPage uuid session
        ]
    ]

sessionHome uuid session = do
    nullDir
    method GET

    let uuid' = ID.toString uuid
    Tpl.inspector ok "UUID" session uuid $ \langs -> H.h1 $ string uuid'

session404 uuid = do
    Tpl.page notFound ["404", "Amphiarao"] $ \langs -> do
        H.h1 $ l langs SessionNotFound
        Tpl.sessionForm langs

setTimeout uuid session = do
    nullDir
    method POST
    timeout <- lookRead "pageLoad"
    let inner s = return $ s {timeouts = (timeouts s) {pageLoad = Just timeout}}
    liftIO $ modifyMVar_ session inner
    seeOther ('/':ID.toString uuid) $ toResponse ()

searchSession uuid session = do
    nullDir
    method GET
    q <- look "q"
    session' <- liftIO $ readMVar session
    let results = [(header, labelEmpty $ engine q session') | (header, engine) <- Q.engines]
    Tpl.inspector ok (Txt.pack ('🔎':q)) session uuid $ \langs -> H.main $ do
        H.aside $ do
            H.form $ do
                H.input H.! A.type_ "search" H.! A.name "q" H.! A.value (H.stringValue q)
            H.dl $ do
                forM results $ \(header, results') -> do
                    H.dt $ header langs
                    forM results' $ \result -> H.dd $ result langs
                    return ()
                return ()
        H.section $ do
            H.iframe H.! A.src "/preview-prompt" H.! A.name "preview" $ ""
  where
    labelEmpty [] = [\langs -> l langs NoResults]
    labelEmpty x = x

loadPage uuid session = do
    nullDir
    method POST
    target <- look "url"
    case Load.parseAbsoluteURI target of
        Just url -> do
            liftIO $ Load.load session url
            seeOther ('/':ID.toString uuid) $ toResponse ()
        Nothing -> Tpl.inspector ok "400" session uuid $ \langs -> l langs ErrURL