{- | Wuss is a library that lets you easily create secure WebSocket clients over the WSS protocol. It is a small addition to and is adapted from existing solutions by , , and . == Example > import Wuss > > import Control.Concurrent (forkIO) > import Control.Monad (forever, unless, void) > import Data.Text (Text, pack) > import Network.WebSockets (ClientApp, receiveData, sendClose, sendTextData) > > main :: IO () > main = runSecureClient "echo.websocket.org" 443 "/" ws > > ws :: ClientApp () > ws connection = do > putStrLn "Connected!" > > void . forkIO . forever $ do > message <- receiveData connection > print (message :: Text) > > let loop = do > line <- getLine > unless (null line) $ do > sendTextData connection (pack line) > loop > loop > > sendClose connection (pack "Bye!") -} module Wuss ( runSecureClient , runSecureClientWith ) where import qualified Data.ByteString as BS import Data.ByteString.Lazy (toStrict) import qualified Data.ByteString.Lazy as BL import Network.Connection (Connection, ConnectionParams (..), TLSSettings (..), connectTo, connectionGetChunk, connectionPut, initConnectionContext) import Network.Socket (HostName, PortNumber) import Network.WebSockets (ClientApp, ConnectionOptions, Headers, defaultConnectionOptions, runClientWithStream) import Network.WebSockets.Stream (makeStream) {- | A secure replacement for 'Network.WebSockets.runClient'. >>> let app _connection = return () >>> runSecureClient "echo.websocket.org" 443 "/" app -} runSecureClient :: HostName -- ^ Host -> PortNumber -- ^ Port -> String -- ^ Path -> ClientApp a -- ^ Application -> IO a runSecureClient host port path app = let options = defaultConnectionOptions headers = [] in runSecureClientWith host port path options headers app {- | A secure replacement for 'Network.WebSockets.runClientWith'. >>> let options = defaultConnectionOptions >>> let headers = [] >>> let app _connection = return () >>> runSecureClientWith "echo.websocket.org" 443 "/" options headers app -} runSecureClientWith :: HostName -- ^ Host -> PortNumber -- ^ Port -> String -- ^ Path -> ConnectionOptions -- ^ Options -> Headers -- ^ Headers -> ClientApp a -- ^ Application -> IO a runSecureClientWith host port path options headers app = do context <- initConnectionContext connection <- connectTo context (connectionParams host port) stream <- makeStream (reader connection) (writer connection) runClientWithStream stream host path options headers app connectionParams :: HostName -> PortNumber -> ConnectionParams connectionParams host port = ConnectionParams { connectionHostname = host , connectionPort = port , connectionUseSecure = Just tlsSettings , connectionUseSocks = Nothing } tlsSettings :: TLSSettings tlsSettings = TLSSettingsSimple { settingDisableCertificateValidation = False , settingDisableSession = False , settingUseServerName = False } reader :: Connection -> IO (Maybe BS.ByteString) reader connection = fmap Just (connectionGetChunk connection) writer :: Connection -> Maybe BL.ByteString -> IO () writer connection = maybe (return ()) (connectionPut connection . toStrict)