{-# 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.Pinpoint.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)
--
-- Creates a new endpoint for an application or updates the settings and
-- attributes of an existing endpoint for an application. You can also use
-- this operation to define custom attributes for an endpoint. If an update
-- includes one or more values for a custom attribute, Amazon Pinpoint
-- replaces (overwrites) any existing values with the new values.
module Amazonka.Pinpoint.UpdateEndpoint
  ( -- * Creating a Request
    UpdateEndpoint (..),
    newUpdateEndpoint,

    -- * Request Lenses
    updateEndpoint_applicationId,
    updateEndpoint_endpointId,
    updateEndpoint_endpointRequest,

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

    -- * Response Lenses
    updateEndpointResponse_httpStatus,
    updateEndpointResponse_messageBody,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Pinpoint.Types
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'
  { -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    UpdateEndpoint -> Text
applicationId :: Prelude.Text,
    -- | The unique identifier for the endpoint.
    UpdateEndpoint -> Text
endpointId :: Prelude.Text,
    UpdateEndpoint -> EndpointRequest
endpointRequest :: EndpointRequest
  }
  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:
--
-- 'applicationId', 'updateEndpoint_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
--
-- 'endpointId', 'updateEndpoint_endpointId' - The unique identifier for the endpoint.
--
-- 'endpointRequest', 'updateEndpoint_endpointRequest' - Undocumented member.
newUpdateEndpoint ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'endpointId'
  Prelude.Text ->
  -- | 'endpointRequest'
  EndpointRequest ->
  UpdateEndpoint
newUpdateEndpoint :: Text -> Text -> EndpointRequest -> UpdateEndpoint
newUpdateEndpoint
  Text
pApplicationId_
  Text
pEndpointId_
  EndpointRequest
pEndpointRequest_ =
    UpdateEndpoint'
      { $sel:applicationId:UpdateEndpoint' :: Text
applicationId = Text
pApplicationId_,
        $sel:endpointId:UpdateEndpoint' :: Text
endpointId = Text
pEndpointId_,
        $sel:endpointRequest:UpdateEndpoint' :: EndpointRequest
endpointRequest = EndpointRequest
pEndpointRequest_
      }

-- | The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
updateEndpoint_applicationId :: Lens.Lens' UpdateEndpoint Prelude.Text
updateEndpoint_applicationId :: Lens' UpdateEndpoint Text
updateEndpoint_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Text
applicationId :: Text
$sel:applicationId:UpdateEndpoint' :: UpdateEndpoint -> Text
applicationId} -> Text
applicationId) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Text
a -> UpdateEndpoint
s {$sel:applicationId:UpdateEndpoint' :: Text
applicationId = Text
a} :: UpdateEndpoint)

-- | The unique identifier for the endpoint.
updateEndpoint_endpointId :: Lens.Lens' UpdateEndpoint Prelude.Text
updateEndpoint_endpointId :: Lens' UpdateEndpoint Text
updateEndpoint_endpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Text
endpointId :: Text
$sel:endpointId:UpdateEndpoint' :: UpdateEndpoint -> Text
endpointId} -> Text
endpointId) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Text
a -> UpdateEndpoint
s {$sel:endpointId:UpdateEndpoint' :: Text
endpointId = Text
a} :: UpdateEndpoint)

-- | Undocumented member.
updateEndpoint_endpointRequest :: Lens.Lens' UpdateEndpoint EndpointRequest
updateEndpoint_endpointRequest :: Lens' UpdateEndpoint EndpointRequest
updateEndpoint_endpointRequest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {EndpointRequest
endpointRequest :: EndpointRequest
$sel:endpointRequest:UpdateEndpoint' :: UpdateEndpoint -> EndpointRequest
endpointRequest} -> EndpointRequest
endpointRequest) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} EndpointRequest
a -> UpdateEndpoint
s {$sel:endpointRequest:UpdateEndpoint' :: EndpointRequest
endpointRequest = EndpointRequest
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.putJSON (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 ->
          Int -> MessageBody -> UpdateEndpointResponse
UpdateEndpointResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable UpdateEndpoint where
  hashWithSalt :: Int -> UpdateEndpoint -> Int
hashWithSalt Int
_salt UpdateEndpoint' {Text
EndpointRequest
endpointRequest :: EndpointRequest
endpointId :: Text
applicationId :: Text
$sel:endpointRequest:UpdateEndpoint' :: UpdateEndpoint -> EndpointRequest
$sel:endpointId:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:applicationId:UpdateEndpoint' :: UpdateEndpoint -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` EndpointRequest
endpointRequest

instance Prelude.NFData UpdateEndpoint where
  rnf :: UpdateEndpoint -> ()
rnf UpdateEndpoint' {Text
EndpointRequest
endpointRequest :: EndpointRequest
endpointId :: Text
applicationId :: Text
$sel:endpointRequest:UpdateEndpoint' :: UpdateEndpoint -> EndpointRequest
$sel:endpointId:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:applicationId:UpdateEndpoint' :: UpdateEndpoint -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EndpointRequest
endpointRequest

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
"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' {Text
EndpointRequest
endpointRequest :: EndpointRequest
endpointId :: Text
applicationId :: Text
$sel:endpointRequest:UpdateEndpoint' :: UpdateEndpoint -> EndpointRequest
$sel:endpointId:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:applicationId:UpdateEndpoint' :: UpdateEndpoint -> Text
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON EndpointRequest
endpointRequest

instance Data.ToPath UpdateEndpoint where
  toPath :: UpdateEndpoint -> ByteString
toPath UpdateEndpoint' {Text
EndpointRequest
endpointRequest :: EndpointRequest
endpointId :: Text
applicationId :: Text
$sel:endpointRequest:UpdateEndpoint' :: UpdateEndpoint -> EndpointRequest
$sel:endpointId:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:applicationId:UpdateEndpoint' :: UpdateEndpoint -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/endpoints/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
endpointId
      ]

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 response's http status code.
    UpdateEndpointResponse -> Int
httpStatus :: Prelude.Int,
    UpdateEndpointResponse -> MessageBody
messageBody :: MessageBody
  }
  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:
--
-- 'httpStatus', 'updateEndpointResponse_httpStatus' - The response's http status code.
--
-- 'messageBody', 'updateEndpointResponse_messageBody' - Undocumented member.
newUpdateEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'messageBody'
  MessageBody ->
  UpdateEndpointResponse
newUpdateEndpointResponse :: Int -> MessageBody -> UpdateEndpointResponse
newUpdateEndpointResponse Int
pHttpStatus_ MessageBody
pMessageBody_ =
  UpdateEndpointResponse'
    { $sel:httpStatus:UpdateEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:messageBody:UpdateEndpointResponse' :: MessageBody
messageBody = MessageBody
pMessageBody_
    }

-- | 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)

-- | Undocumented member.
updateEndpointResponse_messageBody :: Lens.Lens' UpdateEndpointResponse MessageBody
updateEndpointResponse_messageBody :: Lens' UpdateEndpointResponse MessageBody
updateEndpointResponse_messageBody = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpointResponse' {MessageBody
messageBody :: MessageBody
$sel:messageBody:UpdateEndpointResponse' :: UpdateEndpointResponse -> MessageBody
messageBody} -> MessageBody
messageBody) (\s :: UpdateEndpointResponse
s@UpdateEndpointResponse' {} MessageBody
a -> UpdateEndpointResponse
s {$sel:messageBody:UpdateEndpointResponse' :: MessageBody
messageBody = MessageBody
a} :: UpdateEndpointResponse)

instance Prelude.NFData UpdateEndpointResponse where
  rnf :: UpdateEndpointResponse -> ()
rnf UpdateEndpointResponse' {Int
MessageBody
messageBody :: MessageBody
httpStatus :: Int
$sel:messageBody:UpdateEndpointResponse' :: UpdateEndpointResponse -> MessageBody
$sel:httpStatus:UpdateEndpointResponse' :: UpdateEndpointResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MessageBody
messageBody