aboutsummaryrefslogtreecommitdiff
path: root/server/lib/Uplcg/Main/Server.hs
blob: acf293105c4f5e73156a5c6f4630e8a888b57df9 (plain)
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
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
{-# LANGUAGE OverloadedStrings #-}
module Uplcg.Main.Server
    ( main
    ) where

import           Control.Concurrent.MVar        (MVar)
import qualified Control.Concurrent.MVar        as MVar
import           Control.Concurrent.STM         (STM, TVar, atomically)
import qualified Control.Concurrent.STM         as STM
import           Control.Exception              (bracket)
import           Control.Lens                   ((&), (.~), (^.))
import           Control.Monad                  (forever)
import           Control.Monad.Trans            (liftIO)
import qualified Data.Aeson                     as Aeson
import qualified Data.ByteString                as B
import qualified Data.ByteString.Lazy           as BL
import           Data.Char                      (isAlphaNum)
import           Data.Foldable                  (for_)
import qualified Data.HashMap.Strict            as HMS
import qualified Data.List                      as L
import           Data.Maybe                     (fromMaybe, isNothing)
import           Data.String                    (fromString)
import qualified Data.Text                      as T
import qualified Data.Text.Encoding             as T
import qualified Data.Text.IO                   as T
import qualified Data.Text.Lazy                 as TL
import           Data.Traversable               (for)
import qualified Data.Vector                    as V
import qualified Network.Wai                    as Wai
import qualified Network.Wai.Handler.Warp       as Warp
import qualified Network.Wai.Handler.WebSockets as WaiWs
import qualified Network.WebSockets             as WS
import qualified System.Log.FastLogger          as FL
import           System.Random                  (StdGen, newStdGen)
import           Text.Blaze.Html.Renderer.Text  (renderHtml)
import           Uplcg.BaseUrl                  (BaseUrl)
import qualified Uplcg.BaseUrl                  as BaseUrl
import           Uplcg.Config                   (Config)
import qualified Uplcg.Config                   as Config
import qualified Uplcg.CookieSocket             as CookieSocket
import           Uplcg.Game
import           Uplcg.Messages
import qualified Uplcg.Views                    as Views
import qualified Web.Scotty                     as Scotty

type RoomId = T.Text

type Sink = BL.ByteString -> IO ()

data Room = Room
    { roomId    :: RoomId
    , roomGame  :: TVar Game
    , roomSinks :: TVar (HMS.HashMap PlayerId Sink)
    }

data Server = Server
    { serverConfig       :: Config
    , serverLogger       :: FL.FastLogger
    , serverCookieSocket :: CookieSocket.Handle Player
    , serverCards        :: Cards
    , serverRooms        :: MVar (HMS.HashMap RoomId Room)
    }

readCards :: IO Cards
readCards = Cards
    <$> fmap parseCards (T.readFile "assets/black.txt")
    <*> fmap parseCards (T.readFile "assets/white.txt")
  where
    parseCards  = V.fromList . filter (not . T.null) . map dropComment . T.lines
    dropComment = T.strip . fst . T.break (== '#')

withServer :: Config -> FL.FastLogger -> (Server -> IO a) -> IO a
withServer conf fl f = CookieSocket.withHandle 5 $ \cs -> do
    f =<< Server conf fl cs <$> readCards <*> MVar.newMVar HMS.empty

newRoom :: RoomId -> Cards -> StdGen -> STM Room
newRoom rid cards gen = Room rid
    <$> STM.newTVar (newGame cards gen)
    <*> STM.newTVar HMS.empty

parseRoomId :: T.Text -> Either String T.Text
parseRoomId txt
    | T.all isAlphaNum txt && l >= 6 && l <= 32 = Right txt
    | otherwise                                 = Left "Bad room name"
  where
    l = T.length txt

roomViews :: Server -> IO [Views.RoomView]
roomViews server = do
    rooms <- liftIO . MVar.readMVar $ serverRooms server
    liftIO . for (HMS.toList rooms) $ \(rid, room) ->
        fmap (Views.RoomView rid . HMS.size) . atomically . STM.readTVar $
        roomSinks room

scottyApp :: Server -> IO Wai.Application
scottyApp server = Scotty.scottyApp $ do
    Scotty.get "/" $
        Scotty.redirect $ TL.fromStrict $
            BaseUrl.render (Config.cBaseUrl $ serverConfig server) <> "/rooms"

    Scotty.get "/rooms" $ do
        views <- liftIO $ roomViews server
        Scotty.html . renderHtml $ Views.rooms (serverConfig server) views

    Scotty.get "/rooms/:id/" $ do
        rid <- Scotty.param "id" >>=
            either (Scotty.raise . TL.pack) pure . parseRoomId
        Scotty.html . renderHtml $ Views.client (serverConfig server) rid

    Scotty.get "/assets/client.js" $ do
        Scotty.setHeader "Content-Type" "application/JavaScript"
        Scotty.file "assets/client.js"

    Scotty.get "/assets/style.css" $ do
        Scotty.setHeader "Content-Type" "text/css"
        Scotty.file "assets/style.css"

routePendingConnection :: WS.PendingConnection -> Maybe RoomId
routePendingConnection pending =
    let path = T.decodeUtf8 . WS.requestPath $ WS.pendingRequest pending in
    case BaseUrl.parse path of
        BaseUrl.BaseUrl ["rooms", txt, "events"] | Right r <- parseRoomId txt ->
            Just r
        _ -> Nothing

getOrCreateRoom :: Server -> RoomId -> IO Room
getOrCreateRoom server rid = MVar.modifyMVar (serverRooms server) $ \rooms ->
    case HMS.lookup rid rooms of
        Just room -> pure (rooms, room)
        Nothing   -> do
            gen <- newStdGen
            serverLogger server $ "[" <> FL.toLogStr rid <> "] Created room"
            room <- atomically $ newRoom rid (serverCards server) gen
            pure (HMS.insert rid room rooms, room)

deleteRoom :: Server -> RoomId -> IO ()
deleteRoom server rid = do
    serverLogger server $ "[" <> FL.toLogStr rid <> "] Deleting room"
    MVar.modifyMVar_ (serverRooms server) $ pure . HMS.delete rid

joinRoom :: Room -> Sink -> Maybe Player -> STM PlayerId
joinRoom room sink mbRecovered = do
    pid <- STM.stateTVar (roomGame room) $ joinGame mbRecovered
    STM.modifyTVar' (roomSinks room) $ HMS.insert pid sink
    pure pid

leaveRoom :: Room -> PlayerId -> STM (Bool, Maybe Player)
leaveRoom room pid = do
    player <- STM.stateTVar (roomGame room) $ leaveGame pid
    STM.stateTVar (roomSinks room) $ \sinks ->
        let sinks' = HMS.delete pid sinks in
        ((HMS.null sinks', player), sinks')

syncRoom :: Server -> Room -> IO ()
syncRoom server room = do
    (game, sinks) <- atomically $ (,)
        <$> STM.stateTVar (roomGame room) (\g -> (g, g & gameLog .~ []))
        <*> STM.readTVar (roomSinks room)
    for_ (reverse $ game ^. gameLog) $ \msg ->
        serverLogger server $ "[" <> FL.toLogStr (roomId room) <> "] " <>
        FL.toLogStr msg
    for_ (HMS.toList sinks) $ \(pid, sink) -> do
        let view = gameViewForPlayer pid game
        sink . Aeson.encode $ SyncGameView view

wsApp :: Server -> WS.ServerApp
wsApp server pc = case routePendingConnection pc of
    Nothing -> WS.rejectRequest pc "Invalid URL"
    Just rid -> do
        room <- getOrCreateRoom server rid
        (conn, secret, mbRecovered) <-
            CookieSocket.acceptRequest (serverCookieSocket server) rid pc
        let sink = WS.sendTextData conn
        WS.withPingThread conn 30 (pure ()) $ bracket
            (do
                pid <- atomically $ joinRoom room sink mbRecovered
                serverLogger server $ "[" <> FL.toLogStr rid <>
                    "] Player " <> FL.toLogStr pid <>
                    if isNothing mbRecovered then " joined" else " rejoined"
                pure pid)
            (\pid -> do
                (roomEmpty, mbPlayer) <- atomically $ leaveRoom room pid
                serverLogger server $ "[" <> FL.toLogStr rid <>
                    "] Player " <> FL.toLogStr pid <> " left"
                if roomEmpty
                    then deleteRoom server rid
                    else do
                        for_ mbPlayer $ CookieSocket.persist
                            (serverCookieSocket server) secret
                        syncRoom server room)
            (\playerId -> do
                sink . Aeson.encode $ Welcome rid
                syncRoom server room
                cards <- fmap (^. gameCards) . atomically . STM.readTVar $
                    roomGame room
                sink . Aeson.encode $ SyncCards cards
                loop conn rid playerId)
  where
    loop conn rid playerId = forever $ do
        msg <- WS.receiveData conn
        case Aeson.decode msg of
            Just cm -> do
                room <- getOrCreateRoom server rid  -- TODO: only get?
                atomically . STM.modifyTVar' (roomGame room) $
                    processClientMessage playerId cm
                syncRoom server room
            Nothing -> do
                serverLogger server $ "Could not decode client message: " <>
                    FL.toLogStr (show msg)

baseUrl :: BaseUrl -> Wai.Middleware
baseUrl base@(BaseUrl.BaseUrl prefix) application = \req ->
    case L.stripPrefix prefix (Wai.pathInfo req) of
        Nothing   -> application req
        Just path -> application req
            { Wai.pathInfo = path
            , Wai.rawPathInfo = fromMaybe (Wai.rawPathInfo req) .
                B.stripPrefix bs $ Wai.rawPathInfo req
            }
  where
    bs = T.encodeUtf8 $ BaseUrl.render base

main :: IO ()
main = do
    config <- Config.fromEnv
    let settings = Warp.setPort (Config.cPort config) .
            Warp.setHost (fromString $ Config.cHostname config) $
            Warp.defaultSettings
    timeCache <- FL.newTimeCache FL.simpleTimeFormat
    FL.withTimedFastLogger timeCache
            (FL.LogStderr FL.defaultBufSize) $ \tfl ->
        let fl s = tfl (\time -> FL.toLogStr time <> " " <> s <> "\n") in
        withServer config fl $ \server -> do
        sapp <- scottyApp server
        Warp.runSettings settings $ baseUrl (Config.cBaseUrl config) $
            WaiWs.websocketsOr WS.defaultConnectionOptions (wsApp server) sapp