{-# 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.Glue.UpdateDevEndpoint
-- 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 a specified development endpoint.
module Amazonka.Glue.UpdateDevEndpoint
  ( -- * Creating a Request
    UpdateDevEndpoint (..),
    newUpdateDevEndpoint,

    -- * Request Lenses
    updateDevEndpoint_addArguments,
    updateDevEndpoint_addPublicKeys,
    updateDevEndpoint_customLibraries,
    updateDevEndpoint_deleteArguments,
    updateDevEndpoint_deletePublicKeys,
    updateDevEndpoint_publicKey,
    updateDevEndpoint_updateEtlLibraries,
    updateDevEndpoint_endpointName,

    -- * Destructuring the Response
    UpdateDevEndpointResponse (..),
    newUpdateDevEndpointResponse,

    -- * Response Lenses
    updateDevEndpointResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateDevEndpoint' smart constructor.
data UpdateDevEndpoint = UpdateDevEndpoint'
  { -- | The map of arguments to add the map of arguments used to configure the
    -- @DevEndpoint@.
    --
    -- Valid arguments are:
    --
    -- -   @\"--enable-glue-datacatalog\": \"\"@
    --
    -- You can specify a version of Python support for development endpoints by
    -- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
    -- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
    -- defaults to Python 2.
    UpdateDevEndpoint -> Maybe (HashMap Text Text)
addArguments :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The list of public keys for the @DevEndpoint@ to use.
    UpdateDevEndpoint -> Maybe [Text]
addPublicKeys :: Prelude.Maybe [Prelude.Text],
    -- | Custom Python or Java libraries to be loaded in the @DevEndpoint@.
    UpdateDevEndpoint -> Maybe DevEndpointCustomLibraries
customLibraries :: Prelude.Maybe DevEndpointCustomLibraries,
    -- | The list of argument keys to be deleted from the map of arguments used
    -- to configure the @DevEndpoint@.
    UpdateDevEndpoint -> Maybe [Text]
deleteArguments :: Prelude.Maybe [Prelude.Text],
    -- | The list of public keys to be deleted from the @DevEndpoint@.
    UpdateDevEndpoint -> Maybe [Text]
deletePublicKeys :: Prelude.Maybe [Prelude.Text],
    -- | The public key for the @DevEndpoint@ to use.
    UpdateDevEndpoint -> Maybe Text
publicKey :: Prelude.Maybe Prelude.Text,
    -- | @True@ if the list of custom libraries to be loaded in the development
    -- endpoint needs to be updated, or @False@ if otherwise.
    UpdateDevEndpoint -> Maybe Bool
updateEtlLibraries :: Prelude.Maybe Prelude.Bool,
    -- | The name of the @DevEndpoint@ to be updated.
    UpdateDevEndpoint -> Text
endpointName :: Prelude.Text
  }
  deriving (UpdateDevEndpoint -> UpdateDevEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDevEndpoint -> UpdateDevEndpoint -> Bool
$c/= :: UpdateDevEndpoint -> UpdateDevEndpoint -> Bool
== :: UpdateDevEndpoint -> UpdateDevEndpoint -> Bool
$c== :: UpdateDevEndpoint -> UpdateDevEndpoint -> Bool
Prelude.Eq, ReadPrec [UpdateDevEndpoint]
ReadPrec UpdateDevEndpoint
Int -> ReadS UpdateDevEndpoint
ReadS [UpdateDevEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDevEndpoint]
$creadListPrec :: ReadPrec [UpdateDevEndpoint]
readPrec :: ReadPrec UpdateDevEndpoint
$creadPrec :: ReadPrec UpdateDevEndpoint
readList :: ReadS [UpdateDevEndpoint]
$creadList :: ReadS [UpdateDevEndpoint]
readsPrec :: Int -> ReadS UpdateDevEndpoint
$creadsPrec :: Int -> ReadS UpdateDevEndpoint
Prelude.Read, Int -> UpdateDevEndpoint -> ShowS
[UpdateDevEndpoint] -> ShowS
UpdateDevEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDevEndpoint] -> ShowS
$cshowList :: [UpdateDevEndpoint] -> ShowS
show :: UpdateDevEndpoint -> String
$cshow :: UpdateDevEndpoint -> String
showsPrec :: Int -> UpdateDevEndpoint -> ShowS
$cshowsPrec :: Int -> UpdateDevEndpoint -> ShowS
Prelude.Show, forall x. Rep UpdateDevEndpoint x -> UpdateDevEndpoint
forall x. UpdateDevEndpoint -> Rep UpdateDevEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateDevEndpoint x -> UpdateDevEndpoint
$cfrom :: forall x. UpdateDevEndpoint -> Rep UpdateDevEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDevEndpoint' 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:
--
-- 'addArguments', 'updateDevEndpoint_addArguments' - The map of arguments to add the map of arguments used to configure the
-- @DevEndpoint@.
--
-- Valid arguments are:
--
-- -   @\"--enable-glue-datacatalog\": \"\"@
--
-- You can specify a version of Python support for development endpoints by
-- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
-- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
-- defaults to Python 2.
--
-- 'addPublicKeys', 'updateDevEndpoint_addPublicKeys' - The list of public keys for the @DevEndpoint@ to use.
--
-- 'customLibraries', 'updateDevEndpoint_customLibraries' - Custom Python or Java libraries to be loaded in the @DevEndpoint@.
--
-- 'deleteArguments', 'updateDevEndpoint_deleteArguments' - The list of argument keys to be deleted from the map of arguments used
-- to configure the @DevEndpoint@.
--
-- 'deletePublicKeys', 'updateDevEndpoint_deletePublicKeys' - The list of public keys to be deleted from the @DevEndpoint@.
--
-- 'publicKey', 'updateDevEndpoint_publicKey' - The public key for the @DevEndpoint@ to use.
--
-- 'updateEtlLibraries', 'updateDevEndpoint_updateEtlLibraries' - @True@ if the list of custom libraries to be loaded in the development
-- endpoint needs to be updated, or @False@ if otherwise.
--
-- 'endpointName', 'updateDevEndpoint_endpointName' - The name of the @DevEndpoint@ to be updated.
newUpdateDevEndpoint ::
  -- | 'endpointName'
  Prelude.Text ->
  UpdateDevEndpoint
newUpdateDevEndpoint :: Text -> UpdateDevEndpoint
newUpdateDevEndpoint Text
pEndpointName_ =
  UpdateDevEndpoint'
    { $sel:addArguments:UpdateDevEndpoint' :: Maybe (HashMap Text Text)
addArguments = forall a. Maybe a
Prelude.Nothing,
      $sel:addPublicKeys:UpdateDevEndpoint' :: Maybe [Text]
addPublicKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:customLibraries:UpdateDevEndpoint' :: Maybe DevEndpointCustomLibraries
customLibraries = forall a. Maybe a
Prelude.Nothing,
      $sel:deleteArguments:UpdateDevEndpoint' :: Maybe [Text]
deleteArguments = forall a. Maybe a
Prelude.Nothing,
      $sel:deletePublicKeys:UpdateDevEndpoint' :: Maybe [Text]
deletePublicKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:publicKey:UpdateDevEndpoint' :: Maybe Text
publicKey = forall a. Maybe a
Prelude.Nothing,
      $sel:updateEtlLibraries:UpdateDevEndpoint' :: Maybe Bool
updateEtlLibraries = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointName:UpdateDevEndpoint' :: Text
endpointName = Text
pEndpointName_
    }

-- | The map of arguments to add the map of arguments used to configure the
-- @DevEndpoint@.
--
-- Valid arguments are:
--
-- -   @\"--enable-glue-datacatalog\": \"\"@
--
-- You can specify a version of Python support for development endpoints by
-- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
-- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
-- defaults to Python 2.
updateDevEndpoint_addArguments :: Lens.Lens' UpdateDevEndpoint (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateDevEndpoint_addArguments :: Lens' UpdateDevEndpoint (Maybe (HashMap Text Text))
updateDevEndpoint_addArguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Maybe (HashMap Text Text)
addArguments :: Maybe (HashMap Text Text)
$sel:addArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe (HashMap Text Text)
addArguments} -> Maybe (HashMap Text Text)
addArguments) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Maybe (HashMap Text Text)
a -> UpdateDevEndpoint
s {$sel:addArguments:UpdateDevEndpoint' :: Maybe (HashMap Text Text)
addArguments = Maybe (HashMap Text Text)
a} :: UpdateDevEndpoint) 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 list of public keys for the @DevEndpoint@ to use.
updateDevEndpoint_addPublicKeys :: Lens.Lens' UpdateDevEndpoint (Prelude.Maybe [Prelude.Text])
updateDevEndpoint_addPublicKeys :: Lens' UpdateDevEndpoint (Maybe [Text])
updateDevEndpoint_addPublicKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Maybe [Text]
addPublicKeys :: Maybe [Text]
$sel:addPublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
addPublicKeys} -> Maybe [Text]
addPublicKeys) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Maybe [Text]
a -> UpdateDevEndpoint
s {$sel:addPublicKeys:UpdateDevEndpoint' :: Maybe [Text]
addPublicKeys = Maybe [Text]
a} :: UpdateDevEndpoint) 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

-- | Custom Python or Java libraries to be loaded in the @DevEndpoint@.
updateDevEndpoint_customLibraries :: Lens.Lens' UpdateDevEndpoint (Prelude.Maybe DevEndpointCustomLibraries)
updateDevEndpoint_customLibraries :: Lens' UpdateDevEndpoint (Maybe DevEndpointCustomLibraries)
updateDevEndpoint_customLibraries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Maybe DevEndpointCustomLibraries
customLibraries :: Maybe DevEndpointCustomLibraries
$sel:customLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe DevEndpointCustomLibraries
customLibraries} -> Maybe DevEndpointCustomLibraries
customLibraries) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Maybe DevEndpointCustomLibraries
a -> UpdateDevEndpoint
s {$sel:customLibraries:UpdateDevEndpoint' :: Maybe DevEndpointCustomLibraries
customLibraries = Maybe DevEndpointCustomLibraries
a} :: UpdateDevEndpoint)

-- | The list of argument keys to be deleted from the map of arguments used
-- to configure the @DevEndpoint@.
updateDevEndpoint_deleteArguments :: Lens.Lens' UpdateDevEndpoint (Prelude.Maybe [Prelude.Text])
updateDevEndpoint_deleteArguments :: Lens' UpdateDevEndpoint (Maybe [Text])
updateDevEndpoint_deleteArguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Maybe [Text]
deleteArguments :: Maybe [Text]
$sel:deleteArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
deleteArguments} -> Maybe [Text]
deleteArguments) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Maybe [Text]
a -> UpdateDevEndpoint
s {$sel:deleteArguments:UpdateDevEndpoint' :: Maybe [Text]
deleteArguments = Maybe [Text]
a} :: UpdateDevEndpoint) 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 list of public keys to be deleted from the @DevEndpoint@.
updateDevEndpoint_deletePublicKeys :: Lens.Lens' UpdateDevEndpoint (Prelude.Maybe [Prelude.Text])
updateDevEndpoint_deletePublicKeys :: Lens' UpdateDevEndpoint (Maybe [Text])
updateDevEndpoint_deletePublicKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Maybe [Text]
deletePublicKeys :: Maybe [Text]
$sel:deletePublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
deletePublicKeys} -> Maybe [Text]
deletePublicKeys) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Maybe [Text]
a -> UpdateDevEndpoint
s {$sel:deletePublicKeys:UpdateDevEndpoint' :: Maybe [Text]
deletePublicKeys = Maybe [Text]
a} :: UpdateDevEndpoint) 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 public key for the @DevEndpoint@ to use.
updateDevEndpoint_publicKey :: Lens.Lens' UpdateDevEndpoint (Prelude.Maybe Prelude.Text)
updateDevEndpoint_publicKey :: Lens' UpdateDevEndpoint (Maybe Text)
updateDevEndpoint_publicKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Maybe Text
publicKey :: Maybe Text
$sel:publicKey:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Text
publicKey} -> Maybe Text
publicKey) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Maybe Text
a -> UpdateDevEndpoint
s {$sel:publicKey:UpdateDevEndpoint' :: Maybe Text
publicKey = Maybe Text
a} :: UpdateDevEndpoint)

-- | @True@ if the list of custom libraries to be loaded in the development
-- endpoint needs to be updated, or @False@ if otherwise.
updateDevEndpoint_updateEtlLibraries :: Lens.Lens' UpdateDevEndpoint (Prelude.Maybe Prelude.Bool)
updateDevEndpoint_updateEtlLibraries :: Lens' UpdateDevEndpoint (Maybe Bool)
updateDevEndpoint_updateEtlLibraries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Maybe Bool
updateEtlLibraries :: Maybe Bool
$sel:updateEtlLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Bool
updateEtlLibraries} -> Maybe Bool
updateEtlLibraries) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Maybe Bool
a -> UpdateDevEndpoint
s {$sel:updateEtlLibraries:UpdateDevEndpoint' :: Maybe Bool
updateEtlLibraries = Maybe Bool
a} :: UpdateDevEndpoint)

-- | The name of the @DevEndpoint@ to be updated.
updateDevEndpoint_endpointName :: Lens.Lens' UpdateDevEndpoint Prelude.Text
updateDevEndpoint_endpointName :: Lens' UpdateDevEndpoint Text
updateDevEndpoint_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDevEndpoint' {Text
endpointName :: Text
$sel:endpointName:UpdateDevEndpoint' :: UpdateDevEndpoint -> Text
endpointName} -> Text
endpointName) (\s :: UpdateDevEndpoint
s@UpdateDevEndpoint' {} Text
a -> UpdateDevEndpoint
s {$sel:endpointName:UpdateDevEndpoint' :: Text
endpointName = Text
a} :: UpdateDevEndpoint)

instance Core.AWSRequest UpdateDevEndpoint where
  type
    AWSResponse UpdateDevEndpoint =
      UpdateDevEndpointResponse
  request :: (Service -> Service)
-> UpdateDevEndpoint -> Request UpdateDevEndpoint
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 UpdateDevEndpoint
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateDevEndpoint)))
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 -> UpdateDevEndpointResponse
UpdateDevEndpointResponse'
            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 UpdateDevEndpoint where
  hashWithSalt :: Int -> UpdateDevEndpoint -> Int
hashWithSalt Int
_salt UpdateDevEndpoint' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe DevEndpointCustomLibraries
Text
endpointName :: Text
updateEtlLibraries :: Maybe Bool
publicKey :: Maybe Text
deletePublicKeys :: Maybe [Text]
deleteArguments :: Maybe [Text]
customLibraries :: Maybe DevEndpointCustomLibraries
addPublicKeys :: Maybe [Text]
addArguments :: Maybe (HashMap Text Text)
$sel:endpointName:UpdateDevEndpoint' :: UpdateDevEndpoint -> Text
$sel:updateEtlLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Bool
$sel:publicKey:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Text
$sel:deletePublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:deleteArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:customLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe DevEndpointCustomLibraries
$sel:addPublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:addArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
addArguments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
addPublicKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DevEndpointCustomLibraries
customLibraries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
deleteArguments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
deletePublicKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
publicKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
updateEtlLibraries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointName

instance Prelude.NFData UpdateDevEndpoint where
  rnf :: UpdateDevEndpoint -> ()
rnf UpdateDevEndpoint' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe DevEndpointCustomLibraries
Text
endpointName :: Text
updateEtlLibraries :: Maybe Bool
publicKey :: Maybe Text
deletePublicKeys :: Maybe [Text]
deleteArguments :: Maybe [Text]
customLibraries :: Maybe DevEndpointCustomLibraries
addPublicKeys :: Maybe [Text]
addArguments :: Maybe (HashMap Text Text)
$sel:endpointName:UpdateDevEndpoint' :: UpdateDevEndpoint -> Text
$sel:updateEtlLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Bool
$sel:publicKey:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Text
$sel:deletePublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:deleteArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:customLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe DevEndpointCustomLibraries
$sel:addPublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:addArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
addArguments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
addPublicKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DevEndpointCustomLibraries
customLibraries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
deleteArguments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
deletePublicKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
publicKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
updateEtlLibraries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointName

instance Data.ToHeaders UpdateDevEndpoint where
  toHeaders :: UpdateDevEndpoint -> 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
"AWSGlue.UpdateDevEndpoint" :: 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 UpdateDevEndpoint where
  toJSON :: UpdateDevEndpoint -> Value
toJSON UpdateDevEndpoint' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe DevEndpointCustomLibraries
Text
endpointName :: Text
updateEtlLibraries :: Maybe Bool
publicKey :: Maybe Text
deletePublicKeys :: Maybe [Text]
deleteArguments :: Maybe [Text]
customLibraries :: Maybe DevEndpointCustomLibraries
addPublicKeys :: Maybe [Text]
addArguments :: Maybe (HashMap Text Text)
$sel:endpointName:UpdateDevEndpoint' :: UpdateDevEndpoint -> Text
$sel:updateEtlLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Bool
$sel:publicKey:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe Text
$sel:deletePublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:deleteArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:customLibraries:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe DevEndpointCustomLibraries
$sel:addPublicKeys:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe [Text]
$sel:addArguments:UpdateDevEndpoint' :: UpdateDevEndpoint -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AddArguments" 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 (HashMap Text Text)
addArguments,
            (Key
"AddPublicKeys" 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]
addPublicKeys,
            (Key
"CustomLibraries" 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 DevEndpointCustomLibraries
customLibraries,
            (Key
"DeleteArguments" 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]
deleteArguments,
            (Key
"DeletePublicKeys" 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]
deletePublicKeys,
            (Key
"PublicKey" 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
publicKey,
            (Key
"UpdateEtlLibraries" 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 Bool
updateEtlLibraries,
            forall a. a -> Maybe a
Prelude.Just (Key
"EndpointName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointName)
          ]
      )

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

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

-- | /See:/ 'newUpdateDevEndpointResponse' smart constructor.
data UpdateDevEndpointResponse = UpdateDevEndpointResponse'
  { -- | The response's http status code.
    UpdateDevEndpointResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateDevEndpointResponse -> UpdateDevEndpointResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDevEndpointResponse -> UpdateDevEndpointResponse -> Bool
$c/= :: UpdateDevEndpointResponse -> UpdateDevEndpointResponse -> Bool
== :: UpdateDevEndpointResponse -> UpdateDevEndpointResponse -> Bool
$c== :: UpdateDevEndpointResponse -> UpdateDevEndpointResponse -> Bool
Prelude.Eq, ReadPrec [UpdateDevEndpointResponse]
ReadPrec UpdateDevEndpointResponse
Int -> ReadS UpdateDevEndpointResponse
ReadS [UpdateDevEndpointResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDevEndpointResponse]
$creadListPrec :: ReadPrec [UpdateDevEndpointResponse]
readPrec :: ReadPrec UpdateDevEndpointResponse
$creadPrec :: ReadPrec UpdateDevEndpointResponse
readList :: ReadS [UpdateDevEndpointResponse]
$creadList :: ReadS [UpdateDevEndpointResponse]
readsPrec :: Int -> ReadS UpdateDevEndpointResponse
$creadsPrec :: Int -> ReadS UpdateDevEndpointResponse
Prelude.Read, Int -> UpdateDevEndpointResponse -> ShowS
[UpdateDevEndpointResponse] -> ShowS
UpdateDevEndpointResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDevEndpointResponse] -> ShowS
$cshowList :: [UpdateDevEndpointResponse] -> ShowS
show :: UpdateDevEndpointResponse -> String
$cshow :: UpdateDevEndpointResponse -> String
showsPrec :: Int -> UpdateDevEndpointResponse -> ShowS
$cshowsPrec :: Int -> UpdateDevEndpointResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateDevEndpointResponse x -> UpdateDevEndpointResponse
forall x.
UpdateDevEndpointResponse -> Rep UpdateDevEndpointResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateDevEndpointResponse x -> UpdateDevEndpointResponse
$cfrom :: forall x.
UpdateDevEndpointResponse -> Rep UpdateDevEndpointResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDevEndpointResponse' 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', 'updateDevEndpointResponse_httpStatus' - The response's http status code.
newUpdateDevEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateDevEndpointResponse
newUpdateDevEndpointResponse :: Int -> UpdateDevEndpointResponse
newUpdateDevEndpointResponse Int
pHttpStatus_ =
  UpdateDevEndpointResponse'
    { $sel:httpStatus:UpdateDevEndpointResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData UpdateDevEndpointResponse where
  rnf :: UpdateDevEndpointResponse -> ()
rnf UpdateDevEndpointResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateDevEndpointResponse' :: UpdateDevEndpointResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus