{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.KinesisVideo.GetSignalingChannelEndpoint
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides an endpoint for the specified signaling channel to send and
-- receive messages. This API uses the
-- @SingleMasterChannelEndpointConfiguration@ input parameter, which
-- consists of the @Protocols@ and @Role@ properties.
--
-- @Protocols@ is used to determine the communication mechanism. For
-- example, if you specify @WSS@ as the protocol, this API produces a
-- secure websocket endpoint. If you specify @HTTPS@ as the protocol, this
-- API generates an HTTPS endpoint.
--
-- @Role@ determines the messaging permissions. A @MASTER@ role results in
-- this API generating an endpoint that a client can use to communicate
-- with any of the viewers on the channel. A @VIEWER@ role results in this
-- API generating an endpoint that a client can use to communicate only
-- with a @MASTER@.
module Amazonka.KinesisVideo.GetSignalingChannelEndpoint
  ( -- * Creating a Request
    GetSignalingChannelEndpoint (..),
    newGetSignalingChannelEndpoint,

    -- * Request Lenses
    getSignalingChannelEndpoint_singleMasterChannelEndpointConfiguration,
    getSignalingChannelEndpoint_channelARN,

    -- * Destructuring the Response
    GetSignalingChannelEndpointResponse (..),
    newGetSignalingChannelEndpointResponse,

    -- * Response Lenses
    getSignalingChannelEndpointResponse_resourceEndpointList,
    getSignalingChannelEndpointResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KinesisVideo.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetSignalingChannelEndpoint' smart constructor.
data GetSignalingChannelEndpoint = GetSignalingChannelEndpoint'
  { -- | A structure containing the endpoint configuration for the
    -- @SINGLE_MASTER@ channel type.
    GetSignalingChannelEndpoint
-> Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration :: Prelude.Maybe SingleMasterChannelEndpointConfiguration,
    -- | The Amazon Resource Name (ARN) of the signalling channel for which you
    -- want to get an endpoint.
    GetSignalingChannelEndpoint -> Text
channelARN :: Prelude.Text
  }
  deriving (GetSignalingChannelEndpoint -> GetSignalingChannelEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSignalingChannelEndpoint -> GetSignalingChannelEndpoint -> Bool
$c/= :: GetSignalingChannelEndpoint -> GetSignalingChannelEndpoint -> Bool
== :: GetSignalingChannelEndpoint -> GetSignalingChannelEndpoint -> Bool
$c== :: GetSignalingChannelEndpoint -> GetSignalingChannelEndpoint -> Bool
Prelude.Eq, ReadPrec [GetSignalingChannelEndpoint]
ReadPrec GetSignalingChannelEndpoint
Int -> ReadS GetSignalingChannelEndpoint
ReadS [GetSignalingChannelEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSignalingChannelEndpoint]
$creadListPrec :: ReadPrec [GetSignalingChannelEndpoint]
readPrec :: ReadPrec GetSignalingChannelEndpoint
$creadPrec :: ReadPrec GetSignalingChannelEndpoint
readList :: ReadS [GetSignalingChannelEndpoint]
$creadList :: ReadS [GetSignalingChannelEndpoint]
readsPrec :: Int -> ReadS GetSignalingChannelEndpoint
$creadsPrec :: Int -> ReadS GetSignalingChannelEndpoint
Prelude.Read, Int -> GetSignalingChannelEndpoint -> ShowS
[GetSignalingChannelEndpoint] -> ShowS
GetSignalingChannelEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSignalingChannelEndpoint] -> ShowS
$cshowList :: [GetSignalingChannelEndpoint] -> ShowS
show :: GetSignalingChannelEndpoint -> String
$cshow :: GetSignalingChannelEndpoint -> String
showsPrec :: Int -> GetSignalingChannelEndpoint -> ShowS
$cshowsPrec :: Int -> GetSignalingChannelEndpoint -> ShowS
Prelude.Show, forall x.
Rep GetSignalingChannelEndpoint x -> GetSignalingChannelEndpoint
forall x.
GetSignalingChannelEndpoint -> Rep GetSignalingChannelEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSignalingChannelEndpoint x -> GetSignalingChannelEndpoint
$cfrom :: forall x.
GetSignalingChannelEndpoint -> Rep GetSignalingChannelEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'GetSignalingChannelEndpoint' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'singleMasterChannelEndpointConfiguration', 'getSignalingChannelEndpoint_singleMasterChannelEndpointConfiguration' - A structure containing the endpoint configuration for the
-- @SINGLE_MASTER@ channel type.
--
-- 'channelARN', 'getSignalingChannelEndpoint_channelARN' - The Amazon Resource Name (ARN) of the signalling channel for which you
-- want to get an endpoint.
newGetSignalingChannelEndpoint ::
  -- | 'channelARN'
  Prelude.Text ->
  GetSignalingChannelEndpoint
newGetSignalingChannelEndpoint :: Text -> GetSignalingChannelEndpoint
newGetSignalingChannelEndpoint Text
pChannelARN_ =
  GetSignalingChannelEndpoint'
    { $sel:singleMasterChannelEndpointConfiguration:GetSignalingChannelEndpoint' :: Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:channelARN:GetSignalingChannelEndpoint' :: Text
channelARN = Text
pChannelARN_
    }

-- | A structure containing the endpoint configuration for the
-- @SINGLE_MASTER@ channel type.
getSignalingChannelEndpoint_singleMasterChannelEndpointConfiguration :: Lens.Lens' GetSignalingChannelEndpoint (Prelude.Maybe SingleMasterChannelEndpointConfiguration)
getSignalingChannelEndpoint_singleMasterChannelEndpointConfiguration :: Lens'
  GetSignalingChannelEndpoint
  (Maybe SingleMasterChannelEndpointConfiguration)
getSignalingChannelEndpoint_singleMasterChannelEndpointConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSignalingChannelEndpoint' {Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration :: Maybe SingleMasterChannelEndpointConfiguration
$sel:singleMasterChannelEndpointConfiguration:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint
-> Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration} -> Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration) (\s :: GetSignalingChannelEndpoint
s@GetSignalingChannelEndpoint' {} Maybe SingleMasterChannelEndpointConfiguration
a -> GetSignalingChannelEndpoint
s {$sel:singleMasterChannelEndpointConfiguration:GetSignalingChannelEndpoint' :: Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration = Maybe SingleMasterChannelEndpointConfiguration
a} :: GetSignalingChannelEndpoint)

-- | The Amazon Resource Name (ARN) of the signalling channel for which you
-- want to get an endpoint.
getSignalingChannelEndpoint_channelARN :: Lens.Lens' GetSignalingChannelEndpoint Prelude.Text
getSignalingChannelEndpoint_channelARN :: Lens' GetSignalingChannelEndpoint Text
getSignalingChannelEndpoint_channelARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSignalingChannelEndpoint' {Text
channelARN :: Text
$sel:channelARN:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint -> Text
channelARN} -> Text
channelARN) (\s :: GetSignalingChannelEndpoint
s@GetSignalingChannelEndpoint' {} Text
a -> GetSignalingChannelEndpoint
s {$sel:channelARN:GetSignalingChannelEndpoint' :: Text
channelARN = Text
a} :: GetSignalingChannelEndpoint)

instance Core.AWSRequest GetSignalingChannelEndpoint where
  type
    AWSResponse GetSignalingChannelEndpoint =
      GetSignalingChannelEndpointResponse
  request :: (Service -> Service)
-> GetSignalingChannelEndpoint
-> Request GetSignalingChannelEndpoint
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetSignalingChannelEndpoint
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetSignalingChannelEndpoint)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [ResourceEndpointListItem]
-> Int -> GetSignalingChannelEndpointResponse
GetSignalingChannelEndpointResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ResourceEndpointList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetSignalingChannelEndpoint where
  hashWithSalt :: Int -> GetSignalingChannelEndpoint -> Int
hashWithSalt Int
_salt GetSignalingChannelEndpoint' {Maybe SingleMasterChannelEndpointConfiguration
Text
channelARN :: Text
singleMasterChannelEndpointConfiguration :: Maybe SingleMasterChannelEndpointConfiguration
$sel:channelARN:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint -> Text
$sel:singleMasterChannelEndpointConfiguration:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint
-> Maybe SingleMasterChannelEndpointConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
channelARN

instance Prelude.NFData GetSignalingChannelEndpoint where
  rnf :: GetSignalingChannelEndpoint -> ()
rnf GetSignalingChannelEndpoint' {Maybe SingleMasterChannelEndpointConfiguration
Text
channelARN :: Text
singleMasterChannelEndpointConfiguration :: Maybe SingleMasterChannelEndpointConfiguration
$sel:channelARN:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint -> Text
$sel:singleMasterChannelEndpointConfiguration:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint
-> Maybe SingleMasterChannelEndpointConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf
      Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
channelARN

instance Data.ToHeaders GetSignalingChannelEndpoint where
  toHeaders :: GetSignalingChannelEndpoint -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON GetSignalingChannelEndpoint where
  toJSON :: GetSignalingChannelEndpoint -> Value
toJSON GetSignalingChannelEndpoint' {Maybe SingleMasterChannelEndpointConfiguration
Text
channelARN :: Text
singleMasterChannelEndpointConfiguration :: Maybe SingleMasterChannelEndpointConfiguration
$sel:channelARN:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint -> Text
$sel:singleMasterChannelEndpointConfiguration:GetSignalingChannelEndpoint' :: GetSignalingChannelEndpoint
-> Maybe SingleMasterChannelEndpointConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"SingleMasterChannelEndpointConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SingleMasterChannelEndpointConfiguration
singleMasterChannelEndpointConfiguration,
            forall a. a -> Maybe a
Prelude.Just (Key
"ChannelARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
channelARN)
          ]
      )

instance Data.ToPath GetSignalingChannelEndpoint where
  toPath :: GetSignalingChannelEndpoint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/getSignalingChannelEndpoint"

instance Data.ToQuery GetSignalingChannelEndpoint where
  toQuery :: GetSignalingChannelEndpoint -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newGetSignalingChannelEndpointResponse' smart constructor.
data GetSignalingChannelEndpointResponse = GetSignalingChannelEndpointResponse'
  { -- | A list of endpoints for the specified signaling channel.
    GetSignalingChannelEndpointResponse
-> Maybe [ResourceEndpointListItem]
resourceEndpointList :: Prelude.Maybe [ResourceEndpointListItem],
    -- | The response's http status code.
    GetSignalingChannelEndpointResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSignalingChannelEndpointResponse
-> GetSignalingChannelEndpointResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSignalingChannelEndpointResponse
-> GetSignalingChannelEndpointResponse -> Bool
$c/= :: GetSignalingChannelEndpointResponse
-> GetSignalingChannelEndpointResponse -> Bool
== :: GetSignalingChannelEndpointResponse
-> GetSignalingChannelEndpointResponse -> Bool
$c== :: GetSignalingChannelEndpointResponse
-> GetSignalingChannelEndpointResponse -> Bool
Prelude.Eq, ReadPrec [GetSignalingChannelEndpointResponse]
ReadPrec GetSignalingChannelEndpointResponse
Int -> ReadS GetSignalingChannelEndpointResponse
ReadS [GetSignalingChannelEndpointResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSignalingChannelEndpointResponse]
$creadListPrec :: ReadPrec [GetSignalingChannelEndpointResponse]
readPrec :: ReadPrec GetSignalingChannelEndpointResponse
$creadPrec :: ReadPrec GetSignalingChannelEndpointResponse
readList :: ReadS [GetSignalingChannelEndpointResponse]
$creadList :: ReadS [GetSignalingChannelEndpointResponse]
readsPrec :: Int -> ReadS GetSignalingChannelEndpointResponse
$creadsPrec :: Int -> ReadS GetSignalingChannelEndpointResponse
Prelude.Read, Int -> GetSignalingChannelEndpointResponse -> ShowS
[GetSignalingChannelEndpointResponse] -> ShowS
GetSignalingChannelEndpointResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSignalingChannelEndpointResponse] -> ShowS
$cshowList :: [GetSignalingChannelEndpointResponse] -> ShowS
show :: GetSignalingChannelEndpointResponse -> String
$cshow :: GetSignalingChannelEndpointResponse -> String
showsPrec :: Int -> GetSignalingChannelEndpointResponse -> ShowS
$cshowsPrec :: Int -> GetSignalingChannelEndpointResponse -> ShowS
Prelude.Show, forall x.
Rep GetSignalingChannelEndpointResponse x
-> GetSignalingChannelEndpointResponse
forall x.
GetSignalingChannelEndpointResponse
-> Rep GetSignalingChannelEndpointResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSignalingChannelEndpointResponse x
-> GetSignalingChannelEndpointResponse
$cfrom :: forall x.
GetSignalingChannelEndpointResponse
-> Rep GetSignalingChannelEndpointResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSignalingChannelEndpointResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'resourceEndpointList', 'getSignalingChannelEndpointResponse_resourceEndpointList' - A list of endpoints for the specified signaling channel.
--
-- 'httpStatus', 'getSignalingChannelEndpointResponse_httpStatus' - The response's http status code.
newGetSignalingChannelEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSignalingChannelEndpointResponse
newGetSignalingChannelEndpointResponse :: Int -> GetSignalingChannelEndpointResponse
newGetSignalingChannelEndpointResponse Int
pHttpStatus_ =
  GetSignalingChannelEndpointResponse'
    { $sel:resourceEndpointList:GetSignalingChannelEndpointResponse' :: Maybe [ResourceEndpointListItem]
resourceEndpointList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSignalingChannelEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of endpoints for the specified signaling channel.
getSignalingChannelEndpointResponse_resourceEndpointList :: Lens.Lens' GetSignalingChannelEndpointResponse (Prelude.Maybe [ResourceEndpointListItem])
getSignalingChannelEndpointResponse_resourceEndpointList :: Lens'
  GetSignalingChannelEndpointResponse
  (Maybe [ResourceEndpointListItem])
getSignalingChannelEndpointResponse_resourceEndpointList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSignalingChannelEndpointResponse' {Maybe [ResourceEndpointListItem]
resourceEndpointList :: Maybe [ResourceEndpointListItem]
$sel:resourceEndpointList:GetSignalingChannelEndpointResponse' :: GetSignalingChannelEndpointResponse
-> Maybe [ResourceEndpointListItem]
resourceEndpointList} -> Maybe [ResourceEndpointListItem]
resourceEndpointList) (\s :: GetSignalingChannelEndpointResponse
s@GetSignalingChannelEndpointResponse' {} Maybe [ResourceEndpointListItem]
a -> GetSignalingChannelEndpointResponse
s {$sel:resourceEndpointList:GetSignalingChannelEndpointResponse' :: Maybe [ResourceEndpointListItem]
resourceEndpointList = Maybe [ResourceEndpointListItem]
a} :: GetSignalingChannelEndpointResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The response's http status code.
getSignalingChannelEndpointResponse_httpStatus :: Lens.Lens' GetSignalingChannelEndpointResponse Prelude.Int
getSignalingChannelEndpointResponse_httpStatus :: Lens' GetSignalingChannelEndpointResponse Int
getSignalingChannelEndpointResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSignalingChannelEndpointResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetSignalingChannelEndpointResponse' :: GetSignalingChannelEndpointResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetSignalingChannelEndpointResponse
s@GetSignalingChannelEndpointResponse' {} Int
a -> GetSignalingChannelEndpointResponse
s {$sel:httpStatus:GetSignalingChannelEndpointResponse' :: Int
httpStatus = Int
a} :: GetSignalingChannelEndpointResponse)

instance
  Prelude.NFData
    GetSignalingChannelEndpointResponse
  where
  rnf :: GetSignalingChannelEndpointResponse -> ()
rnf GetSignalingChannelEndpointResponse' {Int
Maybe [ResourceEndpointListItem]
httpStatus :: Int
resourceEndpointList :: Maybe [ResourceEndpointListItem]
$sel:httpStatus:GetSignalingChannelEndpointResponse' :: GetSignalingChannelEndpointResponse -> Int
$sel:resourceEndpointList:GetSignalingChannelEndpointResponse' :: GetSignalingChannelEndpointResponse
-> Maybe [ResourceEndpointListItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ResourceEndpointListItem]
resourceEndpointList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus