Skip to content

Commit 03fd99f

Browse files
committed
add a separate server for operational transformation
1 parent bf12126 commit 03fd99f

17 files changed

+376
-253
lines changed

build.sh

+1-1
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ run . cabal_install ./funblocks-server \
5050
./codeworld-game-api \
5151
./codeworld-prediction \
5252
./codeworld-api \
53-
./codeworld-game-server
53+
./codeworld-collab-server
5454

5555
# Build the JavaScript client code for FunBlocks, the block-based UI.
5656
run . cabal_install --ghcjs ./funblocks-client
File renamed without changes.
File renamed without changes.

codeworld-game-server/codeworld-game-server.cabal codeworld-collab-server/codeworld-collab-server.cabal

+13-2
Original file line numberDiff line numberDiff line change
@@ -10,22 +10,33 @@ Build-type: Simple
1010
Extra-source-files: ChangeLog.md
1111
Cabal-version: >=1.10
1212

13-
Executable codeworld-game-server
13+
Executable codeworld-collab-server
1414
Main-is: Main.hs
1515
Other-modules: CodeWorld.GameServer
1616
Build-depends: base >=4.8 && <4.10,
1717
aeson,
18+
directory,
19+
engine-io,
20+
engine-io-snap,
21+
filepath,
22+
hashable,
23+
http-conduit,
24+
mtl,
25+
ot,
1826
text,
1927
websockets == 0.9.*,
2028
websockets-snap == 0.10.*,
2129
snap-core == 1.0.*,
2230
snap-server == 1.0.*,
31+
socket-io,
32+
stm,
2333
transformers,
2434
bytestring,
2535
random,
2636
unordered-containers,
2737
time,
28-
codeworld-game-api
38+
codeworld-game-api,
39+
codeworld-server
2940
Hs-source-dirs: src
3041
Default-language: Haskell2010
3142
Ghc-options: -threaded -rtsopts "-with-rtsopts=-N"
File renamed without changes.
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
{-# LANGUAGE DeriveGeneric #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
4+
{-
5+
Copyright 2017 The CodeWorld Authors. All rights reserved.
6+
7+
Licensed under the Apache License, Version 2.0 (the "License");
8+
you may not use this file except in compliance with the License.
9+
You may obtain a copy of the License at
10+
11+
http://www.apache.org/licenses/LICENSE-2.0
12+
13+
Unless required by applicable law or agreed to in writing, software
14+
distributed under the License is distributed on an "AS IS" BASIS,
15+
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
16+
See the License for the specific language governing permissions and
17+
limitations under the License.
18+
-}
19+
20+
module CodeWorld.CollabModel where
21+
22+
import qualified Control.Concurrent.STM as STM
23+
import Control.OperationalTransformation.Selection (Selection)
24+
import Control.OperationalTransformation.Server (ServerState)
25+
import Control.OperationalTransformation.Text (TextOperation)
26+
import Data.Aeson
27+
import GHC.Generics (Generic)
28+
import Data.Hashable (Hashable)
29+
import qualified Data.HashMap.Strict as HM
30+
import Data.Text (Text)
31+
import Data.Time.Clock (UTCTime)
32+
33+
data CollabServerState = CollabServerState
34+
{ collabProjects :: STM.TVar CollabProjects
35+
, started :: UTCTime
36+
}
37+
38+
type CollabProjects = HM.HashMap CollabId (STM.TVar CollabProject)
39+
40+
data CollabProject = CollabProject
41+
{ totalUsers :: !Int
42+
, collabKey :: CollabId
43+
, collabState :: ServerState Text TextOperation
44+
, users :: [CollabUserState]
45+
}
46+
47+
data CollabUserState = CollabUserState
48+
{ suserId :: !Text
49+
, suserIdent :: !Text
50+
, userSelection :: !Selection
51+
}
52+
53+
instance ToJSON CollabUserState where
54+
toJSON (CollabUserState _ userIdent' sel) =
55+
object $ [ "name" .= userIdent' ] ++ (if sel == mempty then [] else [ "selection" .= sel ])
56+
57+
newtype CollabId = CollabId { unCollabId :: Text } deriving (Eq, Generic)
58+
59+
instance Hashable CollabId
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,209 @@
1+
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE DeriveGeneric #-}
3+
{-# LANGUAGE LambdaCase #-}
4+
{-# LANGUAGE OverloadedLists #-}
5+
{-# LANGUAGE OverloadedStrings #-}
6+
{-# LANGUAGE RecordWildCards #-}
7+
{-# LANGUAGE ScopedTypeVariables #-}
8+
9+
{-
10+
Copyright 2017 The CodeWorld Authors. All rights reserved.
11+
12+
Licensed under the Apache License, Version 2.0 (the "License");
13+
you may not use this file except in compliance with the License.
14+
You may obtain a copy of the License at
15+
16+
http://www.apache.org/licenses/LICENSE-2.0
17+
18+
Unless required by applicable law or agreed to in writing, software
19+
distributed under the License is distributed on an "AS IS" BASIS,
20+
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
21+
See the License for the specific language governing permissions and
22+
limitations under the License.
23+
-}
24+
25+
module CodeWorld.CollabServer
26+
( initCollabServer
27+
, collabServer
28+
) where
29+
30+
import qualified Control.Concurrent.STM as STM
31+
import Control.Monad (when)
32+
import Control.Monad.State.Strict (StateT)
33+
import Control.Monad.Trans
34+
import Control.Monad.Trans.Reader (ReaderT)
35+
import qualified Control.OperationalTransformation.Selection as Sel
36+
import qualified Control.OperationalTransformation.Server as OTS
37+
import Data.Aeson
38+
import qualified Data.ByteString as B
39+
import qualified Data.ByteString.Char8 as BC
40+
import qualified Data.HashMap.Strict as HM
41+
import Data.Maybe (fromJust)
42+
import Data.Text (Text)
43+
import qualified Data.Text as T
44+
import qualified Data.Text.Encoding as T
45+
import Data.Time.Clock
46+
import DataUtil
47+
import Model
48+
import Network.HTTP.Conduit (simpleHttp)
49+
import qualified Network.SocketIO as SIO
50+
import Snap.Core
51+
import SnapUtil
52+
import System.Directory
53+
import System.FilePath
54+
55+
import CodeWorld.CollabModel
56+
57+
-- Initialize Collab Server
58+
59+
initCollabServer :: IO CollabServerState
60+
initCollabServer = do
61+
started <- getCurrentTime
62+
collabProjects <- STM.newTVarIO HM.empty
63+
return CollabServerState {..}
64+
65+
-- Collaboration requests helpers
66+
67+
getRequestParams :: ClientId -> Snap (User, FilePath)
68+
getRequestParams clientId = do
69+
user <- getUser clientId
70+
mode <- getBuildMode
71+
Just path' <- fmap (splitDirectories . BC.unpack) <$> getParam "path"
72+
Just name <- getParam "name"
73+
let projectId = nameToProjectId $ T.decodeUtf8 name
74+
finalDir = joinPath $ map (dirBase . nameToDirId . T.pack) path'
75+
file = userProjectDir mode (userId user) </> finalDir </> projectFile projectId
76+
case (length path', path' !! 0) of
77+
(0, _) -> return (user, file)
78+
(_, x) | x /= "commentables" -> return (user, file)
79+
80+
initCollaborationHandler :: CollabServerState -> ClientId -> Snap (Text, Text, CollabId)
81+
initCollaborationHandler state clientId = do
82+
(user, filePath) <- getRequestParams clientId
83+
collabHashPath <- liftIO $ BC.unpack <$> B.readFile filePath
84+
let collabHash = take (length collabHashPath - 3) . takeFileName $ collabHashPath
85+
Just (currentUsers :: [UserDump]) <- liftIO $ decodeStrict <$>
86+
B.readFile (collabHashPath <.> "users")
87+
let userIdent' = uuserIdent $ (filter (\x -> uuserId x == userId user) currentUsers) !! 0
88+
Just (project :: Project) <- liftIO $ decodeStrict <$>
89+
B.readFile collabHashPath
90+
liftIO $ addNewCollaborator state (userId user) userIdent' (projectSource project) $
91+
CollabId . T.pack $ collabHash
92+
return ((userId user), userIdent', CollabId . T.pack $ collabHash)
93+
94+
getCollabProject :: CollabServerState -> CollabId -> STM.STM (STM.TVar CollabProject)
95+
getCollabProject state collabHash = do
96+
fromJust . HM.lookup collabHash <$> STM.readTVar (collabProjects state)
97+
98+
addNewCollaborator :: CollabServerState -> Text -> Text -> Text -> CollabId -> IO ()
99+
addNewCollaborator state userId' userIdent' projectSource collabHash = do
100+
let collabUser = CollabUserState userId' userIdent' mempty
101+
STM.atomically $ do
102+
hm <- STM.readTVar $ collabProjects state
103+
case HM.lookup collabHash hm of
104+
Just collabProjectTV -> do
105+
collabProject <- STM.readTVar collabProjectTV
106+
case userId' `elem` (map suserId $ users collabProject) of
107+
True -> do
108+
let collabProject' = collabProject
109+
{ users = map (\x -> if suserId x == userId'
110+
then collabUser
111+
else x) $ users collabProject
112+
}
113+
collabProjectTV' <- STM.newTVar collabProject'
114+
STM.modifyTVar (collabProjects state) $
115+
\x -> HM.adjust (\_ -> collabProjectTV') collabHash x
116+
False -> do
117+
let collabProject' = collabProject
118+
{ totalUsers = totalUsers collabProject + 1
119+
, users = collabUser : users collabProject
120+
}
121+
collabProjectTV' <- STM.newTVar collabProject'
122+
STM.modifyTVar (collabProjects state) $
123+
\x -> HM.adjust (\_ -> collabProjectTV') collabHash x
124+
Nothing -> do
125+
let collabProject = CollabProject
126+
{ totalUsers = 1
127+
, collabKey = collabHash
128+
, collabState = OTS.initialServerState projectSource
129+
, users = [collabUser]
130+
}
131+
collabProjectTV <- STM.newTVar collabProject
132+
STM.modifyTVar (collabProjects state) $
133+
\x -> HM.insert collabHash collabProjectTV x
134+
135+
cleanUp :: CollabServerState -> Text -> STM.TVar CollabProject -> STM.STM ()
136+
cleanUp state userId' collabProjectTV = do
137+
collabProject <- STM.readTVar collabProjectTV
138+
case null (filter ((/= userId') . suserId) $ users collabProject) of
139+
True -> do
140+
STM.modifyTVar collabProjectTV (\collabProject' -> collabProject'
141+
{ totalUsers = 0
142+
, users = []
143+
})
144+
let collabHash = collabKey collabProject
145+
STM.modifyTVar (collabProjects state) $ HM.delete collabHash
146+
False -> do
147+
STM.modifyTVar collabProjectTV (\collabProject' -> collabProject'
148+
{ totalUsers = totalUsers collabProject' - 1
149+
, users = filter ((/= userId') . suserId) $
150+
users collabProject'
151+
})
152+
153+
-- Collaboration requests handler
154+
155+
collabServer :: CollabServerState -> ClientId -> StateT SIO.RoutingTable (ReaderT SIO.Socket Snap) ()
156+
collabServer state clientId = do
157+
(userId', userIdent', collabHash) <- liftSnap $ initCollaborationHandler state clientId
158+
let userHash = hashToId "U" . BC.pack $ (show userId') ++ (show . unCollabId $ collabHash)
159+
SIO.broadcastJSON "set_name" [toJSON userHash, toJSON userIdent']
160+
SIO.broadcast "add_user" userIdent'
161+
SIO.emitJSON "logged_in" []
162+
currentUsers' <- liftIO . STM.atomically $ do
163+
collabProjectTV <- getCollabProject state collabHash
164+
(\x -> map suserIdent $ users x) <$> STM.readTVar collabProjectTV
165+
collabProjectTV' <- liftIO . STM.atomically $ getCollabProject state collabHash
166+
OTS.ServerState rev' doc _ <- liftIO $ collabState <$> STM.readTVarIO collabProjectTV'
167+
SIO.emit "doc" $ object
168+
[ "str" .= doc
169+
, "revision" .= rev'
170+
, "clients" .= currentUsers'
171+
]
172+
173+
SIO.on "operation" $ \rev op (sel :: Sel.Selection) -> do
174+
res <- liftIO . STM.atomically $ do
175+
collabProjectTV <- getCollabProject state collabHash
176+
serverState <- collabState <$> STM.readTVar collabProjectTV
177+
case OTS.applyOperation serverState rev op sel of
178+
Left err -> return $ Left err
179+
Right (op', sel', serverState') -> do
180+
STM.modifyTVar collabProjectTV (\collabProject ->
181+
collabProject { collabState = serverState' })
182+
STM.modifyTVar (collabProjects state) $
183+
\x -> HM.adjust (\_ -> collabProjectTV) collabHash x
184+
return $ Right (op', sel')
185+
case res of
186+
Left _ -> return ()
187+
Right (op', sel') -> do
188+
SIO.emitJSON "ack" []
189+
SIO.broadcastJSON "operation" [toJSON userHash, toJSON op', toJSON sel']
190+
191+
SIO.on "selection" $ \sel -> do
192+
liftIO . STM.atomically $ do
193+
collabProjectTV <- getCollabProject state collabHash
194+
currentUsers <- users <$> STM.readTVar collabProjectTV
195+
let currentUsers'' = map (\x -> if ((/= userId') . suserId) x
196+
then x
197+
else x{ userSelection = sel }) currentUsers
198+
STM.modifyTVar collabProjectTV (\collabProject ->
199+
collabProject { users = currentUsers'' })
200+
STM.modifyTVar (collabProjects state) $
201+
\x -> HM.adjust (\_ -> collabProjectTV) collabHash x
202+
SIO.broadcastJSON "selection" [toJSON userHash, toJSON sel]
203+
204+
SIO.appendDisconnectHandler $ do
205+
liftIO . STM.atomically $ do
206+
collabProjectTV <- getCollabProject state collabHash
207+
cleanUp state userId' collabProjectTV
208+
SIO.broadcast "client_left" userHash
209+
SIO.broadcast "remove_user" userIdent'

codeworld-collab-server/src/Main.hs

+59
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
{-
4+
Copyright 2017 The CodeWorld Authors. All rights reserved.
5+
6+
Licensed under the Apache License, Version 2.0 (the "License");
7+
you may not use this file except in compliance with the License.
8+
You may obtain a copy of the License at
9+
10+
http://www.apache.org/licenses/LICENSE-2.0
11+
12+
Unless required by applicable law or agreed to in writing, software
13+
distributed under the License is distributed on an "AS IS" BASIS,
14+
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15+
See the License for the specific language governing permissions and
16+
limitations under the License.
17+
-}
18+
19+
import Control.Applicative ((<|>))
20+
import Control.Monad (unless)
21+
import qualified Data.Text as T
22+
import qualified Data.Text.IO as T
23+
import qualified Network.SocketIO as SIO
24+
import Network.EngineIO.Snap (snapAPI)
25+
import Snap.Core
26+
import Snap.Http.Server
27+
import System.Directory
28+
29+
import CodeWorld.GameServer
30+
import CodeWorld.CollabServer
31+
import SnapUtil
32+
33+
main :: IO ()
34+
main = do
35+
hasClientId <- doesFileExist "web/clientId.txt"
36+
unless hasClientId $ do
37+
putStrLn "WARNING: Missing web/clientId.txt"
38+
putStrLn "User logins will not function properly!"
39+
40+
clientId <- case hasClientId of
41+
True -> do
42+
txt <- T.readFile "web/clientId.txt"
43+
return . ClientId . Just . T.strip $ txt
44+
False -> do
45+
return $ ClientId Nothing
46+
47+
gameServerState <- initGameServer
48+
collabServerState <- initCollabServer
49+
socketIOHandler <- SIO.initialize snapAPI (collabServer collabServerState clientId)
50+
config <- commandLineConfig $
51+
setPort 9160 $
52+
setErrorLog (ConfigFileLog "log/collab-error.log") $
53+
setAccessLog (ConfigFileLog "log/collab-access.log") $
54+
mempty
55+
httpServe config $
56+
ifTop (gameStats gameServerState) <|>
57+
route [ ("gameserver", gameServer gameServerState)
58+
, ("socket.io" , socketIOHandler)
59+
]

0 commit comments

Comments
 (0)