{-# 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.Comprehend.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)
--
-- Updates information about the specified endpoint. For information about
-- endpoints, see
-- <https://docs.aws.amazon.com/comprehend/latest/dg/manage-endpoints.html Managing endpoints>.
module Amazonka.Comprehend.UpdateEndpoint
  ( -- * Creating a Request
    UpdateEndpoint (..),
    newUpdateEndpoint,

    -- * Request Lenses
    updateEndpoint_desiredDataAccessRoleArn,
    updateEndpoint_desiredInferenceUnits,
    updateEndpoint_desiredModelArn,
    updateEndpoint_endpointArn,

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

    -- * Response Lenses
    updateEndpointResponse_httpStatus,
  )
where

import Amazonka.Comprehend.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'
  { -- | Data access role ARN to use in case the new model is encrypted with a
    -- customer CMK.
    UpdateEndpoint -> Maybe Text
desiredDataAccessRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The desired number of inference units to be used by the model using this
    -- endpoint. Each inference unit represents of a throughput of 100
    -- characters per second.
    UpdateEndpoint -> Maybe Natural
desiredInferenceUnits :: Prelude.Maybe Prelude.Natural,
    -- | The ARN of the new model to use when updating an existing endpoint.
    UpdateEndpoint -> Maybe Text
desiredModelArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Number (ARN) of the endpoint being updated.
    UpdateEndpoint -> Text
endpointArn :: 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:
--
-- 'desiredDataAccessRoleArn', 'updateEndpoint_desiredDataAccessRoleArn' - Data access role ARN to use in case the new model is encrypted with a
-- customer CMK.
--
-- 'desiredInferenceUnits', 'updateEndpoint_desiredInferenceUnits' - The desired number of inference units to be used by the model using this
-- endpoint. Each inference unit represents of a throughput of 100
-- characters per second.
--
-- 'desiredModelArn', 'updateEndpoint_desiredModelArn' - The ARN of the new model to use when updating an existing endpoint.
--
-- 'endpointArn', 'updateEndpoint_endpointArn' - The Amazon Resource Number (ARN) of the endpoint being updated.
newUpdateEndpoint ::
  -- | 'endpointArn'
  Prelude.Text ->
  UpdateEndpoint
newUpdateEndpoint :: Text -> UpdateEndpoint
newUpdateEndpoint Text
pEndpointArn_ =
  UpdateEndpoint'
    { $sel:desiredDataAccessRoleArn:UpdateEndpoint' :: Maybe Text
desiredDataAccessRoleArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:desiredInferenceUnits:UpdateEndpoint' :: Maybe Natural
desiredInferenceUnits = forall a. Maybe a
Prelude.Nothing,
      $sel:desiredModelArn:UpdateEndpoint' :: Maybe Text
desiredModelArn = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointArn:UpdateEndpoint' :: Text
endpointArn = Text
pEndpointArn_
    }

-- | Data access role ARN to use in case the new model is encrypted with a
-- customer CMK.
updateEndpoint_desiredDataAccessRoleArn :: Lens.Lens' UpdateEndpoint (Prelude.Maybe Prelude.Text)
updateEndpoint_desiredDataAccessRoleArn :: Lens' UpdateEndpoint (Maybe Text)
updateEndpoint_desiredDataAccessRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe Text
desiredDataAccessRoleArn :: Maybe Text
$sel:desiredDataAccessRoleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
desiredDataAccessRoleArn} -> Maybe Text
desiredDataAccessRoleArn) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe Text
a -> UpdateEndpoint
s {$sel:desiredDataAccessRoleArn:UpdateEndpoint' :: Maybe Text
desiredDataAccessRoleArn = Maybe Text
a} :: UpdateEndpoint)

-- | The desired number of inference units to be used by the model using this
-- endpoint. Each inference unit represents of a throughput of 100
-- characters per second.
updateEndpoint_desiredInferenceUnits :: Lens.Lens' UpdateEndpoint (Prelude.Maybe Prelude.Natural)
updateEndpoint_desiredInferenceUnits :: Lens' UpdateEndpoint (Maybe Natural)
updateEndpoint_desiredInferenceUnits = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe Natural
desiredInferenceUnits :: Maybe Natural
$sel:desiredInferenceUnits:UpdateEndpoint' :: UpdateEndpoint -> Maybe Natural
desiredInferenceUnits} -> Maybe Natural
desiredInferenceUnits) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe Natural
a -> UpdateEndpoint
s {$sel:desiredInferenceUnits:UpdateEndpoint' :: Maybe Natural
desiredInferenceUnits = Maybe Natural
a} :: UpdateEndpoint)

-- | The ARN of the new model to use when updating an existing endpoint.
updateEndpoint_desiredModelArn :: Lens.Lens' UpdateEndpoint (Prelude.Maybe Prelude.Text)
updateEndpoint_desiredModelArn :: Lens' UpdateEndpoint (Maybe Text)
updateEndpoint_desiredModelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Maybe Text
desiredModelArn :: Maybe Text
$sel:desiredModelArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
desiredModelArn} -> Maybe Text
desiredModelArn) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Maybe Text
a -> UpdateEndpoint
s {$sel:desiredModelArn:UpdateEndpoint' :: Maybe Text
desiredModelArn = Maybe Text
a} :: UpdateEndpoint)

-- | The Amazon Resource Number (ARN) of the endpoint being updated.
updateEndpoint_endpointArn :: Lens.Lens' UpdateEndpoint Prelude.Text
updateEndpoint_endpointArn :: Lens' UpdateEndpoint Text
updateEndpoint_endpointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEndpoint' {Text
endpointArn :: Text
$sel:endpointArn:UpdateEndpoint' :: UpdateEndpoint -> Text
endpointArn} -> Text
endpointArn) (\s :: UpdateEndpoint
s@UpdateEndpoint' {} Text
a -> UpdateEndpoint
s {$sel:endpointArn:UpdateEndpoint' :: Text
endpointArn = 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 -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> 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))
      )

instance Prelude.Hashable UpdateEndpoint where
  hashWithSalt :: Int -> UpdateEndpoint -> Int
hashWithSalt Int
_salt UpdateEndpoint' {Maybe Natural
Maybe Text
Text
endpointArn :: Text
desiredModelArn :: Maybe Text
desiredInferenceUnits :: Maybe Natural
desiredDataAccessRoleArn :: Maybe Text
$sel:endpointArn:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:desiredModelArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
$sel:desiredInferenceUnits:UpdateEndpoint' :: UpdateEndpoint -> Maybe Natural
$sel:desiredDataAccessRoleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
desiredDataAccessRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
desiredInferenceUnits
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
desiredModelArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointArn

instance Prelude.NFData UpdateEndpoint where
  rnf :: UpdateEndpoint -> ()
rnf UpdateEndpoint' {Maybe Natural
Maybe Text
Text
endpointArn :: Text
desiredModelArn :: Maybe Text
desiredInferenceUnits :: Maybe Natural
desiredDataAccessRoleArn :: Maybe Text
$sel:endpointArn:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:desiredModelArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
$sel:desiredInferenceUnits:UpdateEndpoint' :: UpdateEndpoint -> Maybe Natural
$sel:desiredDataAccessRoleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
desiredDataAccessRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
desiredInferenceUnits
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
desiredModelArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointArn

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
"Comprehend_20171127.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 Natural
Maybe Text
Text
endpointArn :: Text
desiredModelArn :: Maybe Text
desiredInferenceUnits :: Maybe Natural
desiredDataAccessRoleArn :: Maybe Text
$sel:endpointArn:UpdateEndpoint' :: UpdateEndpoint -> Text
$sel:desiredModelArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
$sel:desiredInferenceUnits:UpdateEndpoint' :: UpdateEndpoint -> Maybe Natural
$sel:desiredDataAccessRoleArn:UpdateEndpoint' :: UpdateEndpoint -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DesiredDataAccessRoleArn" 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
desiredDataAccessRoleArn,
            (Key
"DesiredInferenceUnits" 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 Natural
desiredInferenceUnits,
            (Key
"DesiredModelArn" 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
desiredModelArn,
            forall a. a -> Maybe a
Prelude.Just (Key
"EndpointArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointArn)
          ]
      )

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

-- | 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
httpStatus :: Int
$sel:httpStatus:UpdateEndpointResponse' :: UpdateEndpointResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus