{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} ----------------------------------------------------------------------------- -- | -- Module : Miso.WebSocket -- Copyright : (C) 2016-2018 David M. Johnson -- License : BSD3-style (see the file LICENSE) -- Maintainer : David M. Johnson -- Stability : experimental -- Portability : non-portable ---------------------------------------------------------------------------- module Miso.WebSocket ( -- * Types WebSocket (..) , URL (..) , Protocols (..) , SocketState (..) , CloseCode (..) , WasClean (..) , Reason (..) ) where import GHC.Generics import Prelude hiding (map) #ifdef __GHCJS__ import GHCJS.Marshal #endif import Miso.String -- | WebSocket connection messages data WebSocket action = WebSocketMessage action | WebSocketClose CloseCode WasClean Reason | WebSocketOpen | WebSocketError MisoString deriving (Show, Eq) -- | URL of Websocket server newtype URL = URL MisoString deriving (Show, Eq) -- | Protocols for Websocket connection newtype Protocols = Protocols [MisoString] deriving (Show, Eq) -- | Wether or not the connection closed was done so cleanly newtype WasClean = WasClean Bool deriving (Show, Eq) -- | Reason for closed connection newtype Reason = Reason MisoString deriving (Show, Eq) -- | `SocketState` corresponding to current WebSocket connection data SocketState = CONNECTING -- ^ 0 | OPEN -- ^ 1 | CLOSING -- ^ 2 | CLOSED -- ^ 3 deriving (Show, Eq, Ord, Enum) -- | Code corresponding to a closed connection -- https://developer.mozilla.org/en-US/docs/Web/API/CloseEvent data CloseCode = CLOSE_NORMAL -- ^ 1000, Normal closure; the connection successfully completed whatever purpose for which it was created. | CLOSE_GOING_AWAY -- ^ 1001, The endpoint is going away, either because of a server failure or because the browser is navigating away from the page that opened the connection. | CLOSE_PROTOCOL_ERROR -- ^ 1002, The endpoint is terminating the connection due to a protocol error. | CLOSE_UNSUPPORTED -- ^ 1003, The connection is being terminated because the endpoint received data of a type it cannot accept (for example, a textonly endpoint received binary data). | CLOSE_NO_STATUS -- ^ 1005, Reserved. Indicates that no status code was provided even though one was expected. | CLOSE_ABNORMAL -- ^ 1006, Reserved. Used to indicate that a connection was closed abnormally (that is, with no close frame being sent) when a status code is expected. | Unsupported_Data -- ^ 1007, The endpoint is terminating the connection because a message was received that contained inconsistent data (e.g., nonUTF8 data within a text message). | Policy_Violation -- ^ 1008, The endpoint is terminating the connection because it received a message that violates its policy. This is a generic status code, used when codes 1003 and 1009 are not suitable. | CLOSE_TOO_LARGE -- ^ 1009, The endpoint is terminating the connection because a data frame was received that is too large. | Missing_Extension -- ^ 1010, The client is terminating the connection because it expected the server to negotiate one or more extension, but the server didn't. | Internal_Error -- ^ 1011, The server is terminating the connection because it encountered an unexpected condition that prevented it from fulfilling the request. | Service_Restart -- ^ 1012, The server is terminating the connection because it is restarting. | Try_Again_Later -- ^ 1013, The server is terminating the connection due to a temporary condition, e.g. it is overloaded and is casting off some of its clients. | TLS_Handshake -- ^ 1015, Reserved. Indicates that the connection was closed due to a failure to perform a TLS handshake (e.g., the server certificate can't be verified). | OtherCode Int -- ^ OtherCode that is reserved and not in the range 0999 deriving (Show, Eq, Generic) #ifdef __GHCJS__ -- Defined here to avoid an orphan instance instance ToJSVal CloseCode instance FromJSVal CloseCode #endif