{-# 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 <djohnson.m@gmail.com>
-- 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 (Int -> WebSocket action -> ShowS
[WebSocket action] -> ShowS
WebSocket action -> String
(Int -> WebSocket action -> ShowS)
-> (WebSocket action -> String)
-> ([WebSocket action] -> ShowS)
-> Show (WebSocket action)
forall action. Show action => Int -> WebSocket action -> ShowS
forall action. Show action => [WebSocket action] -> ShowS
forall action. Show action => WebSocket action -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebSocket action] -> ShowS
$cshowList :: forall action. Show action => [WebSocket action] -> ShowS
show :: WebSocket action -> String
$cshow :: forall action. Show action => WebSocket action -> String
showsPrec :: Int -> WebSocket action -> ShowS
$cshowsPrec :: forall action. Show action => Int -> WebSocket action -> ShowS
Show, WebSocket action -> WebSocket action -> Bool
(WebSocket action -> WebSocket action -> Bool)
-> (WebSocket action -> WebSocket action -> Bool)
-> Eq (WebSocket action)
forall action.
Eq action =>
WebSocket action -> WebSocket action -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebSocket action -> WebSocket action -> Bool
$c/= :: forall action.
Eq action =>
WebSocket action -> WebSocket action -> Bool
== :: WebSocket action -> WebSocket action -> Bool
$c== :: forall action.
Eq action =>
WebSocket action -> WebSocket action -> Bool
Eq)

-- | URL of Websocket server
newtype URL = URL MisoString
  deriving (Int -> URL -> ShowS
[URL] -> ShowS
URL -> String
(Int -> URL -> ShowS)
-> (URL -> String) -> ([URL] -> ShowS) -> Show URL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [URL] -> ShowS
$cshowList :: [URL] -> ShowS
show :: URL -> String
$cshow :: URL -> String
showsPrec :: Int -> URL -> ShowS
$cshowsPrec :: Int -> URL -> ShowS
Show, URL -> URL -> Bool
(URL -> URL -> Bool) -> (URL -> URL -> Bool) -> Eq URL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: URL -> URL -> Bool
$c/= :: URL -> URL -> Bool
== :: URL -> URL -> Bool
$c== :: URL -> URL -> Bool
Eq)

-- | Protocols for Websocket connection
newtype Protocols = Protocols [MisoString]
  deriving (Int -> Protocols -> ShowS
[Protocols] -> ShowS
Protocols -> String
(Int -> Protocols -> ShowS)
-> (Protocols -> String)
-> ([Protocols] -> ShowS)
-> Show Protocols
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Protocols] -> ShowS
$cshowList :: [Protocols] -> ShowS
show :: Protocols -> String
$cshow :: Protocols -> String
showsPrec :: Int -> Protocols -> ShowS
$cshowsPrec :: Int -> Protocols -> ShowS
Show, Protocols -> Protocols -> Bool
(Protocols -> Protocols -> Bool)
-> (Protocols -> Protocols -> Bool) -> Eq Protocols
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Protocols -> Protocols -> Bool
$c/= :: Protocols -> Protocols -> Bool
== :: Protocols -> Protocols -> Bool
$c== :: Protocols -> Protocols -> Bool
Eq)

-- | Wether or not the connection closed was done so cleanly
newtype WasClean = WasClean Bool deriving (Int -> WasClean -> ShowS
[WasClean] -> ShowS
WasClean -> String
(Int -> WasClean -> ShowS)
-> (WasClean -> String) -> ([WasClean] -> ShowS) -> Show WasClean
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WasClean] -> ShowS
$cshowList :: [WasClean] -> ShowS
show :: WasClean -> String
$cshow :: WasClean -> String
showsPrec :: Int -> WasClean -> ShowS
$cshowsPrec :: Int -> WasClean -> ShowS
Show, WasClean -> WasClean -> Bool
(WasClean -> WasClean -> Bool)
-> (WasClean -> WasClean -> Bool) -> Eq WasClean
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WasClean -> WasClean -> Bool
$c/= :: WasClean -> WasClean -> Bool
== :: WasClean -> WasClean -> Bool
$c== :: WasClean -> WasClean -> Bool
Eq)

-- | Reason for closed connection
newtype Reason = Reason MisoString deriving (Int -> Reason -> ShowS
[Reason] -> ShowS
Reason -> String
(Int -> Reason -> ShowS)
-> (Reason -> String) -> ([Reason] -> ShowS) -> Show Reason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Reason] -> ShowS
$cshowList :: [Reason] -> ShowS
show :: Reason -> String
$cshow :: Reason -> String
showsPrec :: Int -> Reason -> ShowS
$cshowsPrec :: Int -> Reason -> ShowS
Show, Reason -> Reason -> Bool
(Reason -> Reason -> Bool)
-> (Reason -> Reason -> Bool) -> Eq Reason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Reason -> Reason -> Bool
$c/= :: Reason -> Reason -> Bool
== :: Reason -> Reason -> Bool
$c== :: Reason -> Reason -> Bool
Eq)

-- | `SocketState` corresponding to current WebSocket connection
data SocketState
  = CONNECTING -- ^ 0
  | OPEN       -- ^ 1
  | CLOSING    -- ^ 2
  | CLOSED     -- ^ 3
  deriving (Int -> SocketState -> ShowS
[SocketState] -> ShowS
SocketState -> String
(Int -> SocketState -> ShowS)
-> (SocketState -> String)
-> ([SocketState] -> ShowS)
-> Show SocketState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SocketState] -> ShowS
$cshowList :: [SocketState] -> ShowS
show :: SocketState -> String
$cshow :: SocketState -> String
showsPrec :: Int -> SocketState -> ShowS
$cshowsPrec :: Int -> SocketState -> ShowS
Show, SocketState -> SocketState -> Bool
(SocketState -> SocketState -> Bool)
-> (SocketState -> SocketState -> Bool) -> Eq SocketState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketState -> SocketState -> Bool
$c/= :: SocketState -> SocketState -> Bool
== :: SocketState -> SocketState -> Bool
$c== :: SocketState -> SocketState -> Bool
Eq, Eq SocketState
Eq SocketState
-> (SocketState -> SocketState -> Ordering)
-> (SocketState -> SocketState -> Bool)
-> (SocketState -> SocketState -> Bool)
-> (SocketState -> SocketState -> Bool)
-> (SocketState -> SocketState -> Bool)
-> (SocketState -> SocketState -> SocketState)
-> (SocketState -> SocketState -> SocketState)
-> Ord SocketState
SocketState -> SocketState -> Bool
SocketState -> SocketState -> Ordering
SocketState -> SocketState -> SocketState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SocketState -> SocketState -> SocketState
$cmin :: SocketState -> SocketState -> SocketState
max :: SocketState -> SocketState -> SocketState
$cmax :: SocketState -> SocketState -> SocketState
>= :: SocketState -> SocketState -> Bool
$c>= :: SocketState -> SocketState -> Bool
> :: SocketState -> SocketState -> Bool
$c> :: SocketState -> SocketState -> Bool
<= :: SocketState -> SocketState -> Bool
$c<= :: SocketState -> SocketState -> Bool
< :: SocketState -> SocketState -> Bool
$c< :: SocketState -> SocketState -> Bool
compare :: SocketState -> SocketState -> Ordering
$ccompare :: SocketState -> SocketState -> Ordering
$cp1Ord :: Eq SocketState
Ord, Int -> SocketState
SocketState -> Int
SocketState -> [SocketState]
SocketState -> SocketState
SocketState -> SocketState -> [SocketState]
SocketState -> SocketState -> SocketState -> [SocketState]
(SocketState -> SocketState)
-> (SocketState -> SocketState)
-> (Int -> SocketState)
-> (SocketState -> Int)
-> (SocketState -> [SocketState])
-> (SocketState -> SocketState -> [SocketState])
-> (SocketState -> SocketState -> [SocketState])
-> (SocketState -> SocketState -> SocketState -> [SocketState])
-> Enum SocketState
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SocketState -> SocketState -> SocketState -> [SocketState]
$cenumFromThenTo :: SocketState -> SocketState -> SocketState -> [SocketState]
enumFromTo :: SocketState -> SocketState -> [SocketState]
$cenumFromTo :: SocketState -> SocketState -> [SocketState]
enumFromThen :: SocketState -> SocketState -> [SocketState]
$cenumFromThen :: SocketState -> SocketState -> [SocketState]
enumFrom :: SocketState -> [SocketState]
$cenumFrom :: SocketState -> [SocketState]
fromEnum :: SocketState -> Int
$cfromEnum :: SocketState -> Int
toEnum :: Int -> SocketState
$ctoEnum :: Int -> SocketState
pred :: SocketState -> SocketState
$cpred :: SocketState -> SocketState
succ :: SocketState -> SocketState
$csucc :: SocketState -> SocketState
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 (Int -> CloseCode -> ShowS
[CloseCode] -> ShowS
CloseCode -> String
(Int -> CloseCode -> ShowS)
-> (CloseCode -> String)
-> ([CloseCode] -> ShowS)
-> Show CloseCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CloseCode] -> ShowS
$cshowList :: [CloseCode] -> ShowS
show :: CloseCode -> String
$cshow :: CloseCode -> String
showsPrec :: Int -> CloseCode -> ShowS
$cshowsPrec :: Int -> CloseCode -> ShowS
Show, CloseCode -> CloseCode -> Bool
(CloseCode -> CloseCode -> Bool)
-> (CloseCode -> CloseCode -> Bool) -> Eq CloseCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CloseCode -> CloseCode -> Bool
$c/= :: CloseCode -> CloseCode -> Bool
== :: CloseCode -> CloseCode -> Bool
$c== :: CloseCode -> CloseCode -> Bool
Eq, (forall x. CloseCode -> Rep CloseCode x)
-> (forall x. Rep CloseCode x -> CloseCode) -> Generic CloseCode
forall x. Rep CloseCode x -> CloseCode
forall x. CloseCode -> Rep CloseCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CloseCode x -> CloseCode
$cfrom :: forall x. CloseCode -> Rep CloseCode x
Generic)

#ifdef __GHCJS__
-- Defined here to avoid an orphan instance
instance ToJSVal CloseCode
instance FromJSVal CloseCode
#endif