module Network.WebSockets.Server
( ServerApp
, runServer
, runServerWith
, makeListenSocket
, makePendingConnection
, makePendingConnectionFromStream
) where
import Control.Concurrent (forkIOWithUnmask)
import Control.Exception (allowInterrupt, bracket,
bracketOnError, finally, mask_,
throwIO)
import Control.Monad (forever, void)
import Network.Socket (Socket)
import qualified Network.Socket as S
import Network.WebSockets.Connection
import Network.WebSockets.Http
import qualified Network.WebSockets.Stream as Stream
import Network.WebSockets.Types
type ServerApp = PendingConnection -> IO ()
runServer :: String
-> Int
-> ServerApp
-> IO ()
runServer host port app = runServerWith host port defaultConnectionOptions app
runServerWith :: String -> Int -> ConnectionOptions -> ServerApp -> IO ()
runServerWith host port opts app = S.withSocketsDo $
bracket
(makeListenSocket host port)
S.sClose
(\sock ->
mask_ $ forever $ do
allowInterrupt
(conn, _) <- S.accept sock
void $ forkIOWithUnmask $ \unmask ->
finally (unmask $ runApp conn opts app) (S.sClose conn)
)
makeListenSocket :: String -> Int -> IO Socket
makeListenSocket host port = bracketOnError
(S.socket S.AF_INET S.Stream S.defaultProtocol)
S.sClose
(\sock -> do
_ <- S.setSocketOption sock S.ReuseAddr 1
_ <- S.setSocketOption sock S.NoDelay 1
host' <- S.inet_addr host
S.bindSocket sock (S.SockAddrInet (fromIntegral port) host')
S.listen sock 5
return sock
)
runApp :: Socket
-> ConnectionOptions
-> ServerApp
-> IO ()
runApp socket opts app =
bracket
(makePendingConnection socket opts)
(Stream.close . pendingStream)
app
makePendingConnection
:: Socket -> ConnectionOptions -> IO PendingConnection
makePendingConnection socket opts = do
stream <- Stream.makeSocketStream socket
makePendingConnectionFromStream stream opts
makePendingConnectionFromStream
:: Stream.Stream -> ConnectionOptions -> IO PendingConnection
makePendingConnectionFromStream stream opts = do
mbRequest <- Stream.parse stream (decodeRequestHead False)
case mbRequest of
Nothing -> throwIO ConnectionClosed
Just request -> return PendingConnection
{ pendingOptions = opts
, pendingRequest = request
, pendingOnAccept = \_ -> return ()
, pendingStream = stream
}