{-# 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.CloudWatchEvents.UpdateEndpoint
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Update an existing endpoint. For more information about global
-- endpoints, see
-- <https://docs.aws.amazon.com/eventbridge/latest/userguide/eb-global-endpoints.html Making applications Regional-fault tolerant with global endpoints and event replication>
-- in the Amazon EventBridge User Guide..
module Amazonka.CloudWatchEvents.UpdateEndpoint
  ( -- * Creating a Request
    UpdateEndpoint (..),
    newUpdateEndpoint,

    -- * Request Lenses
    updateEndpoint_description,
    updateEndpoint_eventBuses,
    updateEndpoint_replicationConfig,
    updateEndpoint_roleArn,
    updateEndpoint_routingConfig,
    updateEndpoint_name,

    -- * Destructuring the Response
    UpdateEndpointResponse (..),
    newUpdateEndpointResponse,

    -- * Response Lenses
    updateEndpointResponse_arn,
    updateEndpointResponse_endpointId,
    updateEndpointResponse_endpointUrl,
    updateEndpointResponse_eventBuses,
    updateEndpointResponse_name,
    updateEndpointResponse_replicationConfig,
    updateEndpointResponse_roleArn,
    updateEndpointResponse_routingConfig,
    updateEndpointResponse_state,
    updateEndpointResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateEndpoint' smart constructor.
data UpdateEndpoint = UpdateEndpoint'
  { -- | A description for the endpoint.
    UpdateEndpoint -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Define event buses used for replication.
    UpdateEndpoint -> Maybe (NonEmpty EndpointEventBus)
eventBuses :: Prelude.Maybe (Prelude.NonEmpty EndpointEventBus),
    -- | Whether event replication was enabled or disabled by this request.
    UpdateEndpoint -> Maybe ReplicationConfig
replicationConfig :: Prelude.Maybe ReplicationConfig,
    -- | The ARN of the role used by event replication for this request.
    UpdateEndpoint -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | Configure the routing policy, including the health check and secondary
    -- Region..
    UpdateEndpoint -> Maybe RoutingConfig
routingConfig :: Prelude.Maybe RoutingConfig,
    -- | The name of the endpoint you want to update.
    UpdateEndpoint -> Text
name :: Prelude.Text
  }
  deriving (UpdateEndpoint -> UpdateEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEndpoint -> UpdateEndpoint -> Bool
$c/= :: UpdateEndpoint -> UpdateEndpoint -> Bool
== :: UpdateEndpoint -> UpdateEndpoint -> Bool
$c== :: UpdateEndpoint -> UpdateEndpoint -> Bool
Prelude.Eq, ReadPrec [UpdateEndpoint]
ReadPrec UpdateEndpoint
Int -> ReadS UpdateEndpoint
ReadS [UpdateEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEndpoint]
$creadListPrec :: ReadPrec [UpdateEndpoint]
readPrec :: ReadPrec UpdateEndpoint
$creadPrec :: ReadPrec UpdateEndpoint
readList :: ReadS [UpdateEndpoint]
$creadList :: ReadS [UpdateEndpoint]
readsPrec :: Int -> ReadS UpdateEndpoint
$creadsPrec :: Int -> ReadS UpdateEndpoint
Prelude.Read, Int -> UpdateEndpoint -> ShowS
[UpdateEndpoint] -> ShowS
UpdateEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEndpoint] -> ShowS
$cshowList :: [UpdateEndpoint] -> ShowS
show :: UpdateEndpoint -> String
$cshow :: UpdateEndpoint -> String
showsPrec :: Int -> UpdateEndpoint -> ShowS
$cshowsPrec :: Int -> UpdateEndpoint -> ShowS
Prelude.Show, forall x. Rep UpdateEndpoint x -> UpdateEndpoint
forall x. UpdateEndpoint -> Rep UpdateEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateEndpoint x -> UpdateEndpoint
$cfrom :: forall x. UpdateEndpoint -> Rep UpdateEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEndpoint' 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:
--
-- 'description', 'updateEndpoint_description' - A description for the endpoint.
--
-- 'eventBuses', 'updateEndpoint_eventBuses' - Define event buses used for replication.
--
-- 'replicationConfig', 'updateEndpoint_replicationConfig' - Whether event replication was enabled or disabled by this request.
--
-- 'roleArn', 'updateEndpoint_roleArn' - The ARN of the role used by event replication for this request.
--
-- 'routingConfig', 'updateEndpoint_routingConfig' - Configure the routing policy, including the health check and secondary
-- Region..
--
-- 'name', 'updateEndpoint_name' - The name of the endpoint you want to update.
newUpdateEndpoint ::
  -- | 'name'
  Prelude.Text ->
  UpdateEndpoint
newUpdateEndpoint :: Text -> UpdateEndpoint
newUpdateEndpoint Text
pName_ =
  UpdateEndpoint'
    { $sel:description:UpdateEndpoint' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:eventBuses:UpdateEndpoint' :: Maybe (NonEmpty EndpointEventBus)
eventBuses = forall a. Maybe a
Prelude.Nothing,
      $sel:replicationConfig:UpdateEndpoint' :: Maybe ReplicationConfig
replicationConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:UpdateEndpoint' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:routingConfig:UpdateEndpoint' :: Maybe RoutingConfig
routingConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateEndpoint' :: Text
name = Text
pName_
    }

-- | A description for the endpoint.
updateEndpoint_description :: Lens.Lens' UpdateEndpoint (Prelude.Maybe Prelude.Text)
updateEndpoint_description :: Lens' UpdateEndpoint (Maybe Text)
updateEndpoint_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe Text
description :: Maybe Text
$sel:description:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe Text
a -> UpdateEndpoint
s {$sel:description:UpdateEndpoint' :: Maybe Text
description = Maybe Text
a} :: UpdateEndpoint)

-- | Define event buses used for replication.
updateEndpoint_eventBuses :: Lens.Lens' UpdateEndpoint (Prelude.Maybe (Prelude.NonEmpty EndpointEventBus))
updateEndpoint_eventBuses :: Lens' UpdateEndpoint (Maybe (NonEmpty EndpointEventBus))
updateEndpoint_eventBuses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe (NonEmpty EndpointEventBus)
eventBuses :: Maybe (NonEmpty EndpointEventBus)
$sel:eventBuses:UpdateEndpoint' :: UpdateEndpoint -> Maybe (NonEmpty EndpointEventBus)
eventBuses} -> Maybe (NonEmpty EndpointEventBus)
eventBuses) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe (NonEmpty EndpointEventBus)
a -> UpdateEndpoint
s {$sel:eventBuses:UpdateEndpoint' :: Maybe (NonEmpty EndpointEventBus)
eventBuses = Maybe (NonEmpty EndpointEventBus)
a} :: UpdateEndpoint) 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

-- | Whether event replication was enabled or disabled by this request.
updateEndpoint_replicationConfig :: Lens.Lens' UpdateEndpoint (Prelude.Maybe ReplicationConfig)
updateEndpoint_replicationConfig :: Lens' UpdateEndpoint (Maybe ReplicationConfig)
updateEndpoint_replicationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe ReplicationConfig
replicationConfig :: Maybe ReplicationConfig
$sel:replicationConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe ReplicationConfig
replicationConfig} -> Maybe ReplicationConfig
replicationConfig) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe ReplicationConfig
a -> UpdateEndpoint
s {$sel:replicationConfig:UpdateEndpoint' :: Maybe ReplicationConfig
replicationConfig = Maybe ReplicationConfig
a} :: UpdateEndpoint)

-- | The ARN of the role used by event replication for this request.
updateEndpoint_roleArn :: Lens.Lens' UpdateEndpoint (Prelude.Maybe Prelude.Text)
updateEndpoint_roleArn :: Lens' UpdateEndpoint (Maybe Text)
updateEndpoint_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe Text
a -> UpdateEndpoint
s {$sel:roleArn:UpdateEndpoint' :: Maybe Text
roleArn = Maybe Text
a} :: UpdateEndpoint)

-- | Configure the routing policy, including the health check and secondary
-- Region..
updateEndpoint_routingConfig :: Lens.Lens' UpdateEndpoint (Prelude.Maybe RoutingConfig)
updateEndpoint_routingConfig :: Lens' UpdateEndpoint (Maybe RoutingConfig)
updateEndpoint_routingConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe RoutingConfig
routingConfig :: Maybe RoutingConfig
$sel:routingConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe RoutingConfig
routingConfig} -> Maybe RoutingConfig
routingConfig) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe RoutingConfig
a -> UpdateEndpoint
s {$sel:routingConfig:UpdateEndpoint' :: Maybe RoutingConfig
routingConfig = Maybe RoutingConfig
a} :: UpdateEndpoint)

-- | The name of the endpoint you want to update.
updateEndpoint_name :: Lens.Lens' UpdateEndpoint Prelude.Text
updateEndpoint_name :: Lens' UpdateEndpoint Text
updateEndpoint_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Text
name :: Text
$sel:name:UpdateEndpoint' :: UpdateEndpoint -> Text
name} -> Text
name) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Text
a -> UpdateEndpoint
s {$sel:name:UpdateEndpoint' :: Text
name = Text
a} :: UpdateEndpoint)

instance Core.AWSRequest UpdateEndpoint where
  type
    AWSResponse UpdateEndpoint =
      UpdateEndpointResponse
  request :: (Service -> Service) -> UpdateEndpoint -> Request UpdateEndpoint
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 UpdateEndpoint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateEndpoint)))
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 Text
-> Maybe Text
-> Maybe Text
-> Maybe (NonEmpty EndpointEventBus)
-> Maybe Text
-> Maybe ReplicationConfig
-> Maybe Text
-> Maybe RoutingConfig
-> Maybe EndpointState
-> Int
-> UpdateEndpointResponse
UpdateEndpointResponse'
            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
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EndpointId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EndpointUrl")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EventBuses")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ReplicationConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoutingConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"State")
            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 UpdateEndpoint where
  hashWithSalt :: Int -> UpdateEndpoint -> Int
hashWithSalt Int
_salt UpdateEndpoint' {Maybe (NonEmpty EndpointEventBus)
Maybe Text
Maybe ReplicationConfig
Maybe RoutingConfig
Text
name :: Text
routingConfig :: Maybe RoutingConfig
roleArn :: Maybe Text
replicationConfig :: Maybe ReplicationConfig
eventBuses :: Maybe (NonEmpty EndpointEventBus)
description :: Maybe Text
$sel:name:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:routingConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe RoutingConfig
$sel:roleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
$sel:replicationConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe ReplicationConfig
$sel:eventBuses:UpdateEndpoint' :: UpdateEndpoint -> Maybe (NonEmpty EndpointEventBus)
$sel:description:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty EndpointEventBus)
eventBuses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReplicationConfig
replicationConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RoutingConfig
routingConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData UpdateEndpoint where
  rnf :: UpdateEndpoint -> ()
rnf UpdateEndpoint' {Maybe (NonEmpty EndpointEventBus)
Maybe Text
Maybe ReplicationConfig
Maybe RoutingConfig
Text
name :: Text
routingConfig :: Maybe RoutingConfig
roleArn :: Maybe Text
replicationConfig :: Maybe ReplicationConfig
eventBuses :: Maybe (NonEmpty EndpointEventBus)
description :: Maybe Text
$sel:name:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:routingConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe RoutingConfig
$sel:roleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
$sel:replicationConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe ReplicationConfig
$sel:eventBuses:UpdateEndpoint' :: UpdateEndpoint -> Maybe (NonEmpty EndpointEventBus)
$sel:description:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty EndpointEventBus)
eventBuses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReplicationConfig
replicationConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RoutingConfig
routingConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders UpdateEndpoint where
  toHeaders :: UpdateEndpoint -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"AWSEvents.UpdateEndpoint" :: Prelude.ByteString),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateEndpoint where
  toJSON :: UpdateEndpoint -> Value
toJSON UpdateEndpoint' {Maybe (NonEmpty EndpointEventBus)
Maybe Text
Maybe ReplicationConfig
Maybe RoutingConfig
Text
name :: Text
routingConfig :: Maybe RoutingConfig
roleArn :: Maybe Text
replicationConfig :: Maybe ReplicationConfig
eventBuses :: Maybe (NonEmpty EndpointEventBus)
description :: Maybe Text
$sel:name:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:routingConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe RoutingConfig
$sel:roleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
$sel:replicationConfig:UpdateEndpoint' :: UpdateEndpoint -> Maybe ReplicationConfig
$sel:eventBuses:UpdateEndpoint' :: UpdateEndpoint -> Maybe (NonEmpty EndpointEventBus)
$sel:description:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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 Text
description,
            (Key
"EventBuses" 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 (NonEmpty EndpointEventBus)
eventBuses,
            (Key
"ReplicationConfig" 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 ReplicationConfig
replicationConfig,
            (Key
"RoleArn" 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 Text
roleArn,
            (Key
"RoutingConfig" 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 RoutingConfig
routingConfig,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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

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

-- | /See:/ 'newUpdateEndpointResponse' smart constructor.
data UpdateEndpointResponse = UpdateEndpointResponse'
  { -- | The ARN of the endpoint you updated in this request.
    UpdateEndpointResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the endpoint you updated in this request.
    UpdateEndpointResponse -> Maybe Text
endpointId :: Prelude.Maybe Prelude.Text,
    -- | The URL of the endpoint you updated in this request.
    UpdateEndpointResponse -> Maybe Text
endpointUrl :: Prelude.Maybe Prelude.Text,
    -- | The event buses used for replication for the endpoint you updated in
    -- this request.
    UpdateEndpointResponse -> Maybe (NonEmpty EndpointEventBus)
eventBuses :: Prelude.Maybe (Prelude.NonEmpty EndpointEventBus),
    -- | The name of the endpoint you updated in this request.
    UpdateEndpointResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Whether event replication was enabled or disabled for the endpoint you
    -- updated in this request.
    UpdateEndpointResponse -> Maybe ReplicationConfig
replicationConfig :: Prelude.Maybe ReplicationConfig,
    -- | The ARN of the role used by event replication for the endpoint you
    -- updated in this request.
    UpdateEndpointResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The routing configuration you updated in this request.
    UpdateEndpointResponse -> Maybe RoutingConfig
routingConfig :: Prelude.Maybe RoutingConfig,
    -- | The state of the endpoint you updated in this request.
    UpdateEndpointResponse -> Maybe EndpointState
state :: Prelude.Maybe EndpointState,
    -- | The response's http status code.
    UpdateEndpointResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateEndpointResponse -> UpdateEndpointResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEndpointResponse -> UpdateEndpointResponse -> Bool
$c/= :: UpdateEndpointResponse -> UpdateEndpointResponse -> Bool
== :: UpdateEndpointResponse -> UpdateEndpointResponse -> Bool
$c== :: UpdateEndpointResponse -> UpdateEndpointResponse -> Bool
Prelude.Eq, ReadPrec [UpdateEndpointResponse]
ReadPrec UpdateEndpointResponse
Int -> ReadS UpdateEndpointResponse
ReadS [UpdateEndpointResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEndpointResponse]
$creadListPrec :: ReadPrec [UpdateEndpointResponse]
readPrec :: ReadPrec UpdateEndpointResponse
$creadPrec :: ReadPrec UpdateEndpointResponse
readList :: ReadS [UpdateEndpointResponse]
$creadList :: ReadS [UpdateEndpointResponse]
readsPrec :: Int -> ReadS UpdateEndpointResponse
$creadsPrec :: Int -> ReadS UpdateEndpointResponse
Prelude.Read, Int -> UpdateEndpointResponse -> ShowS
[UpdateEndpointResponse] -> ShowS
UpdateEndpointResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEndpointResponse] -> ShowS
$cshowList :: [UpdateEndpointResponse] -> ShowS
show :: UpdateEndpointResponse -> String
$cshow :: UpdateEndpointResponse -> String
showsPrec :: Int -> UpdateEndpointResponse -> ShowS
$cshowsPrec :: Int -> UpdateEndpointResponse -> ShowS
Prelude.Show, forall x. Rep UpdateEndpointResponse x -> UpdateEndpointResponse
forall x. UpdateEndpointResponse -> Rep UpdateEndpointResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateEndpointResponse x -> UpdateEndpointResponse
$cfrom :: forall x. UpdateEndpointResponse -> Rep UpdateEndpointResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEndpointResponse' 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:
--
-- 'arn', 'updateEndpointResponse_arn' - The ARN of the endpoint you updated in this request.
--
-- 'endpointId', 'updateEndpointResponse_endpointId' - The ID of the endpoint you updated in this request.
--
-- 'endpointUrl', 'updateEndpointResponse_endpointUrl' - The URL of the endpoint you updated in this request.
--
-- 'eventBuses', 'updateEndpointResponse_eventBuses' - The event buses used for replication for the endpoint you updated in
-- this request.
--
-- 'name', 'updateEndpointResponse_name' - The name of the endpoint you updated in this request.
--
-- 'replicationConfig', 'updateEndpointResponse_replicationConfig' - Whether event replication was enabled or disabled for the endpoint you
-- updated in this request.
--
-- 'roleArn', 'updateEndpointResponse_roleArn' - The ARN of the role used by event replication for the endpoint you
-- updated in this request.
--
-- 'routingConfig', 'updateEndpointResponse_routingConfig' - The routing configuration you updated in this request.
--
-- 'state', 'updateEndpointResponse_state' - The state of the endpoint you updated in this request.
--
-- 'httpStatus', 'updateEndpointResponse_httpStatus' - The response's http status code.
newUpdateEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateEndpointResponse
newUpdateEndpointResponse :: Int -> UpdateEndpointResponse
newUpdateEndpointResponse Int
pHttpStatus_ =
  UpdateEndpointResponse'
    { $sel:arn:UpdateEndpointResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointId:UpdateEndpointResponse' :: Maybe Text
endpointId = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointUrl:UpdateEndpointResponse' :: Maybe Text
endpointUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:eventBuses:UpdateEndpointResponse' :: Maybe (NonEmpty EndpointEventBus)
eventBuses = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateEndpointResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:replicationConfig:UpdateEndpointResponse' :: Maybe ReplicationConfig
replicationConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:UpdateEndpointResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:routingConfig:UpdateEndpointResponse' :: Maybe RoutingConfig
routingConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:state:UpdateEndpointResponse' :: Maybe EndpointState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the endpoint you updated in this request.
updateEndpointResponse_arn :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe Prelude.Text)
updateEndpointResponse_arn :: Lens' UpdateEndpointResponse (Maybe Text)
updateEndpointResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe Text
a -> UpdateEndpointResponse
s {$sel:arn:UpdateEndpointResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateEndpointResponse)

-- | The ID of the endpoint you updated in this request.
updateEndpointResponse_endpointId :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe Prelude.Text)
updateEndpointResponse_endpointId :: Lens' UpdateEndpointResponse (Maybe Text)
updateEndpointResponse_endpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe Text
endpointId :: Maybe Text
$sel:endpointId:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
endpointId} -> Maybe Text
endpointId) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe Text
a -> UpdateEndpointResponse
s {$sel:endpointId:UpdateEndpointResponse' :: Maybe Text
endpointId = Maybe Text
a} :: UpdateEndpointResponse)

-- | The URL of the endpoint you updated in this request.
updateEndpointResponse_endpointUrl :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe Prelude.Text)
updateEndpointResponse_endpointUrl :: Lens' UpdateEndpointResponse (Maybe Text)
updateEndpointResponse_endpointUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe Text
endpointUrl :: Maybe Text
$sel:endpointUrl:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
endpointUrl} -> Maybe Text
endpointUrl) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe Text
a -> UpdateEndpointResponse
s {$sel:endpointUrl:UpdateEndpointResponse' :: Maybe Text
endpointUrl = Maybe Text
a} :: UpdateEndpointResponse)

-- | The event buses used for replication for the endpoint you updated in
-- this request.
updateEndpointResponse_eventBuses :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe (Prelude.NonEmpty EndpointEventBus))
updateEndpointResponse_eventBuses :: Lens' UpdateEndpointResponse (Maybe (NonEmpty EndpointEventBus))
updateEndpointResponse_eventBuses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe (NonEmpty EndpointEventBus)
eventBuses :: Maybe (NonEmpty EndpointEventBus)
$sel:eventBuses:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe (NonEmpty EndpointEventBus)
eventBuses} -> Maybe (NonEmpty EndpointEventBus)
eventBuses) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe (NonEmpty EndpointEventBus)
a -> UpdateEndpointResponse
s {$sel:eventBuses:UpdateEndpointResponse' :: Maybe (NonEmpty EndpointEventBus)
eventBuses = Maybe (NonEmpty EndpointEventBus)
a} :: UpdateEndpointResponse) 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 name of the endpoint you updated in this request.
updateEndpointResponse_name :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe Prelude.Text)
updateEndpointResponse_name :: Lens' UpdateEndpointResponse (Maybe Text)
updateEndpointResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe Text
name :: Maybe Text
$sel:name:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe Text
a -> UpdateEndpointResponse
s {$sel:name:UpdateEndpointResponse' :: Maybe Text
name = Maybe Text
a} :: UpdateEndpointResponse)

-- | Whether event replication was enabled or disabled for the endpoint you
-- updated in this request.
updateEndpointResponse_replicationConfig :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe ReplicationConfig)
updateEndpointResponse_replicationConfig :: Lens' UpdateEndpointResponse (Maybe ReplicationConfig)
updateEndpointResponse_replicationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe ReplicationConfig
replicationConfig :: Maybe ReplicationConfig
$sel:replicationConfig:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe ReplicationConfig
replicationConfig} -> Maybe ReplicationConfig
replicationConfig) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe ReplicationConfig
a -> UpdateEndpointResponse
s {$sel:replicationConfig:UpdateEndpointResponse' :: Maybe ReplicationConfig
replicationConfig = Maybe ReplicationConfig
a} :: UpdateEndpointResponse)

-- | The ARN of the role used by event replication for the endpoint you
-- updated in this request.
updateEndpointResponse_roleArn :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe Prelude.Text)
updateEndpointResponse_roleArn :: Lens' UpdateEndpointResponse (Maybe Text)
updateEndpointResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe Text
a -> UpdateEndpointResponse
s {$sel:roleArn:UpdateEndpointResponse' :: Maybe Text
roleArn = Maybe Text
a} :: UpdateEndpointResponse)

-- | The routing configuration you updated in this request.
updateEndpointResponse_routingConfig :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe RoutingConfig)
updateEndpointResponse_routingConfig :: Lens' UpdateEndpointResponse (Maybe RoutingConfig)
updateEndpointResponse_routingConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe RoutingConfig
routingConfig :: Maybe RoutingConfig
$sel:routingConfig:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe RoutingConfig
routingConfig} -> Maybe RoutingConfig
routingConfig) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe RoutingConfig
a -> UpdateEndpointResponse
s {$sel:routingConfig:UpdateEndpointResponse' :: Maybe RoutingConfig
routingConfig = Maybe RoutingConfig
a} :: UpdateEndpointResponse)

-- | The state of the endpoint you updated in this request.
updateEndpointResponse_state :: Lens.Lens' UpdateEndpointResponse (Prelude.Maybe EndpointState)
updateEndpointResponse_state :: Lens' UpdateEndpointResponse (Maybe EndpointState)
updateEndpointResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {Maybe EndpointState
state :: Maybe EndpointState
$sel:state:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe EndpointState
state} -> Maybe EndpointState
state) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} Maybe EndpointState
a -> UpdateEndpointResponse
s {$sel:state:UpdateEndpointResponse' :: Maybe EndpointState
state = Maybe EndpointState
a} :: UpdateEndpointResponse)

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

instance Prelude.NFData UpdateEndpointResponse where
  rnf :: UpdateEndpointResponse -> ()
rnf UpdateEndpointResponse' {Int
Maybe (NonEmpty EndpointEventBus)
Maybe Text
Maybe EndpointState
Maybe ReplicationConfig
Maybe RoutingConfig
httpStatus :: Int
state :: Maybe EndpointState
routingConfig :: Maybe RoutingConfig
roleArn :: Maybe Text
replicationConfig :: Maybe ReplicationConfig
name :: Maybe Text
eventBuses :: Maybe (NonEmpty EndpointEventBus)
endpointUrl :: Maybe Text
endpointId :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:UpdateEndpointResponse' :: UpdateEndpointResponse -> Int
$sel:state:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe EndpointState
$sel:routingConfig:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe RoutingConfig
$sel:roleArn:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
$sel:replicationConfig:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe ReplicationConfig
$sel:name:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
$sel:eventBuses:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe (NonEmpty EndpointEventBus)
$sel:endpointUrl:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
$sel:endpointId:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
$sel:arn:UpdateEndpointResponse' :: UpdateEndpointResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpointId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpointUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty EndpointEventBus)
eventBuses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReplicationConfig
replicationConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RoutingConfig
routingConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EndpointState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus