blob: 13b1f6bfb22283ee2cc6f324343f2b0bc13c4bcb (
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
|
{-# LANGUAGE OverloadedStrings #-}
module Cafp.Main.Server
( main
) where
import Cafp.Game
import Cafp.Messages
import Control.Concurrent (threadDelay)
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, when)
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import Data.Foldable (for_)
import qualified Data.HashMap.Strict as HMS
import Data.Text (Text)
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 qualified Data.Vector as V
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.IO as IO
import qualified Web.Scotty as Scotty
warning :: String -> IO ()
warning = IO.hPutStrLn IO.stderr
type RoomId = T.Text
type Sink = BL.ByteString -> IO ()
data Room = Room
{ roomGame :: TVar Game
, roomSinks :: TVar (HMS.HashMap PlayerId Sink)
}
data Server = Server
{ serverCards :: Cards
, serverRooms :: TVar (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.isPrefixOf "#") . filter (not . T.null) . T.lines
newServer :: IO Server
newServer = Server <$> readCards <*> atomically (STM.newTVar HMS.empty)
newRoom :: Server -> STM Room
newRoom server = Room
<$> STM.newTVar (newGame $ serverCards server)
<*> STM.newTVar HMS.empty
scottyApp :: IO Wai.Application
scottyApp = Scotty.scottyApp $ do
Scotty.get "/rooms/:id/" $ do
roomId <- Scotty.param "id"
when (T.length roomId < 6) $
Scotty.raise "Room ID should be at least 6 characters"
Scotty.setHeader "Content-Type" "text/html"
Scotty.file "assets/client.html"
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 T.split (== '/') path of
[_, "rooms", roomId, "events"] -> Just roomId
_ -> Nothing
getOrCreateRoom :: Server -> RoomId -> STM Room
getOrCreateRoom server roomId = do
rooms <- STM.readTVar $ serverRooms server
case HMS.lookup roomId rooms of
Just room -> pure room
Nothing -> do
room <- newRoom server
STM.writeTVar (serverRooms server) $ HMS.insert roomId room rooms
pure room
joinRoom :: Room -> Sink -> STM PlayerId
joinRoom room sink = do
pid <- STM.stateTVar (roomGame room) joinGame
STM.modifyTVar' (roomSinks room) $ HMS.insert pid sink
pure pid
leaveRoom :: Room -> PlayerId -> STM ()
leaveRoom room pid = do
STM.modifyTVar' (roomGame room) $ leaveGame pid
STM.modifyTVar' (roomSinks room) $ HMS.delete pid
syncRoom :: Room -> IO ()
syncRoom room = do
(game, sinks) <- atomically $ (,)
<$> STM.readTVar (roomGame room)
<*> STM.readTVar (roomSinks room)
warning $ "New state: " ++ show game
for_ (HMS.toList sinks) $ \(pid, sink) ->
sink . Aeson.encode . SyncGameView $ gameViewForPlayer pid game
wsApp :: Server -> WS.ServerApp
wsApp server pc = case routePendingConnection pc of
Nothing -> WS.rejectRequest pc "Invalid URL"
Just roomId -> do
room <- atomically $ getOrCreateRoom server roomId
conn <- WS.acceptRequest pc
let sink = WS.sendTextData conn
WS.withPingThread conn 30 (pure ()) $ bracket
(atomically $ joinRoom room sink)
(\playerId -> do
atomically $ leaveRoom room playerId
syncRoom room)
(\playerId -> do
syncRoom room
cards <- fmap (^. gameCards) . atomically . STM.readTVar $
roomGame room
sink . Aeson.encode $ SyncCards cards
loop conn roomId playerId)
where
loop conn roomId playerId = forever $ do
msg <- WS.receiveData conn
case Aeson.decode msg of
Just cm -> do
warning $ "Client: " ++ show cm
room <- atomically $ do
room <- getOrCreateRoom server roomId
STM.modifyTVar' (roomGame room) $
processClientMessage playerId cm
pure room
syncRoom room
Nothing -> do
warning $ "Could not decode client message: " ++ show msg
main :: IO ()
main = do
let port = 3000
settings = Warp.setPort port Warp.defaultSettings
server <- newServer
sapp <- scottyApp
Warp.runSettings settings $
WaiWs.websocketsOr WS.defaultConnectionOptions (wsApp server) sapp
|