ReaderT
This commit is contained in:
parent
cdfc0849cf
commit
839f6df5f8
|
@ -4,3 +4,11 @@
|
||||||
|
|
||||||
`stack build`
|
`stack build`
|
||||||
`stack stack run`
|
`stack stack run`
|
||||||
|
|
||||||
|
## Debug
|
||||||
|
|
||||||
|
Using websocat
|
||||||
|
|
||||||
|
`websocat ws://127.0.0.1:9160`
|
||||||
|
|
||||||
|
`curl --data 'body data' localhost:8081`
|
||||||
|
|
|
@ -26,6 +26,11 @@ dependencies:
|
||||||
- http-types
|
- http-types
|
||||||
- warp
|
- warp
|
||||||
- websockets
|
- websockets
|
||||||
|
- aeson
|
||||||
|
- text
|
||||||
|
- bytestring
|
||||||
|
- uuid
|
||||||
|
- lifted-base
|
||||||
|
|
||||||
ghc-options:
|
ghc-options:
|
||||||
- -Wall
|
- -Wall
|
||||||
|
|
|
@ -1,14 +1,24 @@
|
||||||
|
{-# LANGUAGE DerivingVia #-}
|
||||||
|
|
||||||
module Lib
|
module Lib
|
||||||
( runBothServers,
|
( runBothServers,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
|
import Types.AppTypes
|
||||||
import WebServer (runWebServer)
|
import WebServer (runWebServer)
|
||||||
import WebSocket (initMVarState, runWebSocketServer)
|
import WebSocket (initMVarState, runWebSocketServer)
|
||||||
|
|
||||||
runBothServers :: IO ()
|
runBothServers :: IO ()
|
||||||
runBothServers = do
|
runBothServers = do
|
||||||
mVarState <- initMVarState
|
connectedClientsState <- initMVarState
|
||||||
_ <- concurrently (runWebSocketServer mVarState) (runWebServer mVarState)
|
|
||||||
|
let env =
|
||||||
|
Env
|
||||||
|
{ connectedClientsState = connectedClientsState,
|
||||||
|
profile = Dev
|
||||||
|
}
|
||||||
|
|
||||||
|
_ <- concurrently (unApp runWebSocketServer env) (unApp runWebServer env)
|
||||||
return ()
|
return ()
|
||||||
|
|
29
backend/src/Types/AppTypes.hs
Normal file
29
backend/src/Types/AppTypes.hs
Normal file
|
@ -0,0 +1,29 @@
|
||||||
|
{-# LANGUAGE DerivingVia #-}
|
||||||
|
|
||||||
|
module Types.AppTypes (Env (..), App (..), getConnectedClientState, HasConnectedClientState, App, AppProfile (Prod, Dev)) where
|
||||||
|
|
||||||
|
import ClassyPrelude
|
||||||
|
import Types.ConnectionState (ConnectedClientsState)
|
||||||
|
|
||||||
|
data AppProfile = Prod | Dev
|
||||||
|
|
||||||
|
data Env = Env
|
||||||
|
{ connectedClientsState :: ConnectedClientsState,
|
||||||
|
profile :: AppProfile
|
||||||
|
}
|
||||||
|
|
||||||
|
class HasConnectedClientState a where
|
||||||
|
getConnectedClientState :: a -> ConnectedClientsState
|
||||||
|
|
||||||
|
instance HasConnectedClientState Env where
|
||||||
|
getConnectedClientState = connectedClientsState
|
||||||
|
|
||||||
|
newtype App env a = App {unApp :: env -> IO a}
|
||||||
|
deriving
|
||||||
|
( Functor,
|
||||||
|
Applicative,
|
||||||
|
Monad,
|
||||||
|
MonadReader env,
|
||||||
|
MonadIO
|
||||||
|
)
|
||||||
|
via ReaderT env IO
|
21
backend/src/Types/ConnectionState.hs
Normal file
21
backend/src/Types/ConnectionState.hs
Normal file
|
@ -0,0 +1,21 @@
|
||||||
|
module Types.ConnectionState
|
||||||
|
( Client (..),
|
||||||
|
Client,
|
||||||
|
ConnectedClientsState,
|
||||||
|
ConnectedClients,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import ClassyPrelude
|
||||||
|
import Data.UUID (UUID)
|
||||||
|
import Network.WebSockets qualified as WS
|
||||||
|
|
||||||
|
data Client = Client
|
||||||
|
{ uuid :: UUID,
|
||||||
|
name :: Text,
|
||||||
|
conn :: WS.Connection
|
||||||
|
}
|
||||||
|
|
||||||
|
type ConnectedClientsState = MVar ConnectedClients
|
||||||
|
|
||||||
|
type ConnectedClients = [Client]
|
18
backend/src/Types/Participant.hs
Normal file
18
backend/src/Types/Participant.hs
Normal file
|
@ -0,0 +1,18 @@
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
|
||||||
|
module Types.Participant (Participant) where
|
||||||
|
|
||||||
|
import ClassyPrelude
|
||||||
|
import Data.Aeson (FromJSON, ToJSON)
|
||||||
|
|
||||||
|
data Participant = Participant
|
||||||
|
{ jid :: Text,
|
||||||
|
email :: Text,
|
||||||
|
displayName :: Text,
|
||||||
|
avatarURL :: Text
|
||||||
|
}
|
||||||
|
deriving (Generic, Show)
|
||||||
|
|
||||||
|
instance ToJSON Participant
|
||||||
|
|
||||||
|
instance FromJSON Participant
|
19
backend/src/Types/RoomData.hs
Normal file
19
backend/src/Types/RoomData.hs
Normal file
|
@ -0,0 +1,19 @@
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
|
||||||
|
module Types.RoomData (RoomData) where
|
||||||
|
|
||||||
|
import ClassyPrelude
|
||||||
|
import Data.Aeson (FromJSON, ToJSON)
|
||||||
|
import Types.Participant (Participant)
|
||||||
|
|
||||||
|
data RoomData = RoomData
|
||||||
|
{ roomName :: RoomName,
|
||||||
|
participants :: [Participant]
|
||||||
|
}
|
||||||
|
deriving (Generic, Show)
|
||||||
|
|
||||||
|
type RoomName = Text
|
||||||
|
|
||||||
|
instance ToJSON RoomData
|
||||||
|
|
||||||
|
instance FromJSON RoomData
|
|
@ -1,25 +1,101 @@
|
||||||
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||||
|
{-# LANGUAGE DerivingVia #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
|
||||||
|
|
||||||
module WebServer (runWebServer) where
|
module WebServer (runWebServer) where
|
||||||
|
|
||||||
import ClassyPrelude
|
-- import AppTypes (HasConnectedClientState)
|
||||||
import Network.HTTP.Types
|
import ClassyPrelude hiding (decodeUtf8)
|
||||||
import Network.Wai
|
import Data.Text.Encoding
|
||||||
import Network.Wai.Handler.Warp (run)
|
import Network.HTTP.Types
|
||||||
import WebSocket (ServerState, broadcast)
|
import Network.Wai
|
||||||
|
import Network.Wai.Handler.Warp (run)
|
||||||
|
import Types.AppTypes (Env (connectedClientsState),
|
||||||
|
HasConnectedClientState (..), unApp)
|
||||||
|
import WebSocket (broadcast)
|
||||||
|
|
||||||
-- todo: use ReaderT instead of curring the state
|
newtype WebApp env a = WebApp {unWebApp :: env -> IO a}
|
||||||
-- then add a MVar for storing the room Data, including users that are not in any room yet
|
deriving
|
||||||
|
( Functor,
|
||||||
|
Applicative,
|
||||||
|
Monad,
|
||||||
|
MonadReader env,
|
||||||
|
MonadIO
|
||||||
|
)
|
||||||
|
via ReaderT env IO
|
||||||
|
|
||||||
app :: MVar ServerState -> Application
|
data WebEnv = WebEnv
|
||||||
app state req respond = do
|
{ appEnv :: Env,
|
||||||
putStrLn "I've done some IO here"
|
request :: Request,
|
||||||
withMVar state $ \currenState -> broadcast "body of req" currenState
|
respond :: Response -> IO ResponseReceived
|
||||||
respond $
|
}
|
||||||
responseLBS
|
|
||||||
status200
|
|
||||||
[("Content-Type", "text/plain")]
|
|
||||||
""
|
|
||||||
|
|
||||||
runWebServer :: MVar ServerState -> IO ()
|
instance HasConnectedClientState WebEnv where
|
||||||
runWebServer state = do
|
getConnectedClientState = connectedClientsState . appEnv
|
||||||
putStrLn "http://localhost:8080/"
|
|
||||||
run 8080 $ app state
|
class HasWebEnv a where
|
||||||
|
getRequest :: a -> Request
|
||||||
|
getRespond :: a -> (Response -> IO ResponseReceived)
|
||||||
|
|
||||||
|
instance HasWebEnv WebEnv where
|
||||||
|
getRequest = request
|
||||||
|
getRespond = respond
|
||||||
|
|
||||||
|
broadCastToClients ::
|
||||||
|
( MonadIO m,
|
||||||
|
HasConnectedClientState env,
|
||||||
|
MonadReader env m
|
||||||
|
) =>
|
||||||
|
Text ->
|
||||||
|
m ()
|
||||||
|
broadCastToClients message = do
|
||||||
|
state <- getConnectedClientState <$> ask
|
||||||
|
liftIO $ withMVar state $ \currenState -> broadcast message currenState
|
||||||
|
|
||||||
|
getRequestBody ::
|
||||||
|
( MonadIO m,
|
||||||
|
HasWebEnv env,
|
||||||
|
MonadReader env m
|
||||||
|
) =>
|
||||||
|
m Text
|
||||||
|
getRequestBody = do
|
||||||
|
request <- getRequest <$> ask
|
||||||
|
liftIO $ (decodeUtf8 . toStrict) <$> consumeRequestBodyStrict request
|
||||||
|
|
||||||
|
app ::
|
||||||
|
( MonadIO m,
|
||||||
|
HasWebEnv env,
|
||||||
|
HasConnectedClientState env,
|
||||||
|
MonadReader env m
|
||||||
|
) =>
|
||||||
|
m ResponseReceived
|
||||||
|
app =
|
||||||
|
do
|
||||||
|
liftIO $ putStrLn "I've done some IO here"
|
||||||
|
getRequestBody >>= broadCastToClients
|
||||||
|
respond' <- getRespond <$> ask
|
||||||
|
liftIO $ respond' $ responseLBS status200 [("Content-Type", "text/plain")] ""
|
||||||
|
|
||||||
|
runWebApp ::
|
||||||
|
( MonadIO m,
|
||||||
|
MonadReader Env m
|
||||||
|
) =>
|
||||||
|
m Application
|
||||||
|
runWebApp = do
|
||||||
|
env <- ask
|
||||||
|
return
|
||||||
|
( \req res -> do
|
||||||
|
let webEnv = WebEnv {appEnv = env, request = req, respond = res}
|
||||||
|
unWebApp app webEnv
|
||||||
|
)
|
||||||
|
|
||||||
|
runWebServer ::
|
||||||
|
( MonadIO m,
|
||||||
|
MonadReader Env m
|
||||||
|
) =>
|
||||||
|
m ()
|
||||||
|
runWebServer = do
|
||||||
|
putStrLn "http://localhost:8081/"
|
||||||
|
runWebApp >>= liftIO . run 8081
|
||||||
|
return ()
|
||||||
|
|
|
@ -1,52 +1,151 @@
|
||||||
module WebSocket (broadcast, initMVarState, runWebSocketServer, ServerState, Client) where
|
{-# LANGUAGE DerivingVia #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
|
||||||
|
module WebSocket (broadcast, initMVarState, runWebSocketServer) where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
|
import Data.UUID (UUID)
|
||||||
|
import Data.UUID.V4 (nextRandom)
|
||||||
import Network.WebSockets qualified as WS
|
import Network.WebSockets qualified as WS
|
||||||
|
import Types.AppTypes
|
||||||
|
( Env (connectedClientsState),
|
||||||
|
HasConnectedClientState (getConnectedClientState),
|
||||||
|
)
|
||||||
|
import Types.ConnectionState
|
||||||
|
( Client (..),
|
||||||
|
ConnectedClients,
|
||||||
|
ConnectedClientsState,
|
||||||
|
)
|
||||||
|
|
||||||
type Client = (Text, WS.Connection)
|
addClient :: Client -> ConnectedClients -> ConnectedClients
|
||||||
|
|
||||||
type ServerState = [Client]
|
|
||||||
|
|
||||||
addClient :: Client -> ServerState -> ServerState
|
|
||||||
addClient client clients = client : clients
|
addClient client clients = client : clients
|
||||||
|
|
||||||
removeClient :: Client -> ServerState -> ServerState
|
removeClient :: UUID -> ConnectedClients -> ConnectedClients
|
||||||
removeClient client = filter ((/= fst client) . fst)
|
removeClient toRemove = filter ((/= toRemove) . uuid)
|
||||||
|
|
||||||
newServerState :: ServerState
|
newConnectedClients :: ConnectedClients
|
||||||
newServerState = []
|
newConnectedClients = []
|
||||||
|
|
||||||
broadcast :: Text -> ServerState -> IO ()
|
broadcast :: Text -> ConnectedClients -> IO ()
|
||||||
broadcast message clients = do
|
broadcast message clients = do
|
||||||
putStrLn message
|
putStrLn message
|
||||||
forM_ clients $ \(_, conn) -> WS.sendTextData conn message
|
forM_ clients $ \client -> WS.sendTextData (conn client) message
|
||||||
|
|
||||||
initMVarState :: IO (MVar ServerState)
|
initMVarState :: IO (MVar ConnectedClients)
|
||||||
initMVarState = newMVar newServerState
|
initMVarState = newMVar newConnectedClients
|
||||||
|
|
||||||
runWebSocketServer :: MVar ServerState -> IO ()
|
runWebSocketServer ::
|
||||||
runWebSocketServer state = do
|
( MonadIO m,
|
||||||
WS.runServer "127.0.0.1" 9160 $ webSocketApplication state
|
MonadReader Env m
|
||||||
|
) =>
|
||||||
|
m ()
|
||||||
|
runWebSocketServer = do
|
||||||
|
putStrLn "Websocket up at 127.0.0.1:9160"
|
||||||
|
state <- getConnectedClientState <$> ask
|
||||||
|
wsApp <- runWSApp
|
||||||
|
liftIO $ WS.runServer "127.0.0.1" 9160 $ wsApp
|
||||||
|
|
||||||
webSocketApplication :: MVar ServerState -> WS.ServerApp
|
runWSApp ::
|
||||||
webSocketApplication state pending = do
|
( MonadIO m,
|
||||||
putStrLn "pending request"
|
MonadReader Env m
|
||||||
conn <- WS.acceptRequest pending
|
) =>
|
||||||
WS.withPingThread conn 30 (return ()) $ do
|
m WS.ServerApp
|
||||||
msg <- WS.receiveData conn
|
runWSApp = do
|
||||||
putStrLn msg
|
env <- ask
|
||||||
let client = ("hall", conn)
|
return
|
||||||
flip finally (disconnect client) $ do
|
( \pending -> do
|
||||||
modifyMVar_ state $ \s -> do
|
putStrLn "pending request"
|
||||||
let s' = addClient client s
|
conn <- WS.acceptRequest pending
|
||||||
return s'
|
uuid <- nextRandom
|
||||||
forever $ do
|
let wsEnv = WSEnv {appEnv = env, connection = conn, clientId = uuid}
|
||||||
currentMsg <- WS.receiveData conn
|
WS.withPingThread conn 30 (return ()) $ do
|
||||||
putStrLn currentMsg
|
unWSApp wsApp wsEnv
|
||||||
where
|
)
|
||||||
disconnect client = do
|
|
||||||
putStrLn "disconnect"
|
newClient ::
|
||||||
modifyMVar state $ \s ->
|
( MonadIO m,
|
||||||
let s' = removeClient client s
|
HasWSEnv env,
|
||||||
in return
|
MonadReader env m
|
||||||
(s', s')
|
) =>
|
||||||
|
Text ->
|
||||||
|
m Client
|
||||||
|
newClient name = do
|
||||||
|
env <- ask
|
||||||
|
return $ Client {uuid = getClientId env, name = name, conn = getConn env}
|
||||||
|
|
||||||
|
newtype WSApp env a = WSApp {unWSApp :: env -> IO a}
|
||||||
|
deriving
|
||||||
|
( Functor,
|
||||||
|
Applicative,
|
||||||
|
Monad,
|
||||||
|
MonadReader env,
|
||||||
|
MonadIO,
|
||||||
|
MonadUnliftIO
|
||||||
|
)
|
||||||
|
via ReaderT env IO
|
||||||
|
|
||||||
|
-- instance MonadBaseControl IO m => MonadBaseControl IO (WSApp env n)
|
||||||
|
-- where
|
||||||
|
|
||||||
|
wsApp ::
|
||||||
|
( HasWSEnv env,
|
||||||
|
HasConnectedClientState env,
|
||||||
|
MonadReader env m,
|
||||||
|
MonadUnliftIO m
|
||||||
|
) =>
|
||||||
|
m ()
|
||||||
|
wsApp = do
|
||||||
|
state <- getConnectedClientState <$> ask
|
||||||
|
msg <- getMessage
|
||||||
|
putStrLn msg
|
||||||
|
client <- newClient msg
|
||||||
|
modifyMVar_ state $ \s -> do
|
||||||
|
let s' = addClient client s
|
||||||
|
return s'
|
||||||
|
flip finally disconnectWsClient $ do
|
||||||
|
forever $ do
|
||||||
|
currentMsg <- getMessage
|
||||||
|
putStrLn currentMsg
|
||||||
|
|
||||||
|
getMessage ::
|
||||||
|
( HasWSEnv env,
|
||||||
|
MonadIO m,
|
||||||
|
MonadReader env m
|
||||||
|
) =>
|
||||||
|
m Text
|
||||||
|
getMessage = do
|
||||||
|
conn' <- getConn <$> ask
|
||||||
|
liftIO $ WS.receiveData conn'
|
||||||
|
|
||||||
|
disconnectWsClient ::
|
||||||
|
( MonadIO m,
|
||||||
|
HasWSEnv env,
|
||||||
|
HasConnectedClientState env,
|
||||||
|
MonadReader env m
|
||||||
|
) =>
|
||||||
|
m ()
|
||||||
|
disconnectWsClient = do
|
||||||
|
clientId <- getClientId <$> ask
|
||||||
|
state <- getConnectedClientState <$> ask
|
||||||
|
liftIO $ modifyMVar state $ \s ->
|
||||||
|
let s' = removeClient clientId s
|
||||||
|
in return
|
||||||
|
(s', ())
|
||||||
|
|
||||||
|
data WSEnv = WSEnv
|
||||||
|
{ appEnv :: Env,
|
||||||
|
connection :: WS.Connection,
|
||||||
|
clientId :: UUID
|
||||||
|
}
|
||||||
|
|
||||||
|
instance HasConnectedClientState WSEnv where
|
||||||
|
getConnectedClientState = connectedClientsState . appEnv
|
||||||
|
|
||||||
|
class HasWSEnv a where
|
||||||
|
getConn :: a -> WS.Connection
|
||||||
|
getClientId :: a -> UUID
|
||||||
|
|
||||||
|
instance HasWSEnv WSEnv where
|
||||||
|
getConn = connection
|
||||||
|
getClientId = clientId
|
||||||
|
|
Loading…
Reference in a new issue