module Network.WebSockets.Socket
( runServer
, runWithSocket
, iterSocket
) where
import Control.Concurrent (forkIO)
import Control.Exception (SomeException, handle)
import Control.Monad (forever)
import Control.Monad.Trans (liftIO)
import Data.ByteString (ByteString)
import Data.Enumerator (Iteratee, ($$))
import Network.Socket (Socket)
import qualified Data.Enumerator as E
import qualified Network.Socket as S
import qualified Network.Socket.ByteString as SB
import qualified Network.Socket.Enumerator as SE
import Network.WebSockets.Handshake.Http
import Network.WebSockets.Monad
import Network.WebSockets.Protocol
import Network.WebSockets.Types
runServer :: Protocol p
=> String
-> Int
-> (Request -> WebSockets p ())
-> IO ()
runServer host port ws = S.withSocketsDo $ do
sock <- S.socket S.AF_INET S.Stream S.defaultProtocol
_ <- S.setSocketOption sock S.ReuseAddr 1
host' <- S.inet_addr host
S.bindSocket sock (S.SockAddrInet (fromIntegral port) host')
S.listen sock 5
handle (closeSock sock) $ forever $ do
(conn, _) <- S.accept sock
_ <- forkIO $ runWithSocket conn ws >> return ()
return ()
where
closeSock :: Socket -> SomeException -> IO ()
closeSock sock _ = S.sClose sock
runWithSocket :: Protocol p
=> Socket -> (Request -> WebSockets p a) -> IO a
runWithSocket s ws = do
r <- E.run $ SE.enumSocket 4096 s $$ runWebSocketsWithHandshake
defaultWebSocketsOptions False ws (iterSocket s)
S.sClose s
either (error . show) return r
iterSocket :: Socket -> Iteratee ByteString IO ()
iterSocket s = E.continue go
where
go (E.Chunks []) = E.continue go
go (E.Chunks cs) = do
b <- liftIO $ S.sIsWritable s
if b
then E.tryIO (SB.sendMany s cs) >> E.continue go
else E.throwError ConnectionClosed
go E.EOF = E.continue go