{-# 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.DataSync.UpdateAgent
-- 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 the name of an agent.
module Amazonka.DataSync.UpdateAgent
  ( -- * Creating a Request
    UpdateAgent (..),
    newUpdateAgent,

    -- * Request Lenses
    updateAgent_name,
    updateAgent_agentArn,

    -- * Destructuring the Response
    UpdateAgentResponse (..),
    newUpdateAgentResponse,

    -- * Response Lenses
    updateAgentResponse_httpStatus,
  )
where

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

-- | UpdateAgentRequest
--
-- /See:/ 'newUpdateAgent' smart constructor.
data UpdateAgent = UpdateAgent'
  { -- | The name that you want to use to configure the agent.
    UpdateAgent -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the agent to update.
    UpdateAgent -> Text
agentArn :: Prelude.Text
  }
  deriving (UpdateAgent -> UpdateAgent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAgent -> UpdateAgent -> Bool
$c/= :: UpdateAgent -> UpdateAgent -> Bool
== :: UpdateAgent -> UpdateAgent -> Bool
$c== :: UpdateAgent -> UpdateAgent -> Bool
Prelude.Eq, ReadPrec [UpdateAgent]
ReadPrec UpdateAgent
Int -> ReadS UpdateAgent
ReadS [UpdateAgent]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateAgent]
$creadListPrec :: ReadPrec [UpdateAgent]
readPrec :: ReadPrec UpdateAgent
$creadPrec :: ReadPrec UpdateAgent
readList :: ReadS [UpdateAgent]
$creadList :: ReadS [UpdateAgent]
readsPrec :: Int -> ReadS UpdateAgent
$creadsPrec :: Int -> ReadS UpdateAgent
Prelude.Read, Int -> UpdateAgent -> ShowS
[UpdateAgent] -> ShowS
UpdateAgent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAgent] -> ShowS
$cshowList :: [UpdateAgent] -> ShowS
show :: UpdateAgent -> String
$cshow :: UpdateAgent -> String
showsPrec :: Int -> UpdateAgent -> ShowS
$cshowsPrec :: Int -> UpdateAgent -> ShowS
Prelude.Show, forall x. Rep UpdateAgent x -> UpdateAgent
forall x. UpdateAgent -> Rep UpdateAgent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateAgent x -> UpdateAgent
$cfrom :: forall x. UpdateAgent -> Rep UpdateAgent x
Prelude.Generic)

-- |
-- Create a value of 'UpdateAgent' 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:
--
-- 'name', 'updateAgent_name' - The name that you want to use to configure the agent.
--
-- 'agentArn', 'updateAgent_agentArn' - The Amazon Resource Name (ARN) of the agent to update.
newUpdateAgent ::
  -- | 'agentArn'
  Prelude.Text ->
  UpdateAgent
newUpdateAgent :: Text -> UpdateAgent
newUpdateAgent Text
pAgentArn_ =
  UpdateAgent'
    { $sel:name:UpdateAgent' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:agentArn:UpdateAgent' :: Text
agentArn = Text
pAgentArn_
    }

-- | The name that you want to use to configure the agent.
updateAgent_name :: Lens.Lens' UpdateAgent (Prelude.Maybe Prelude.Text)
updateAgent_name :: Lens' UpdateAgent (Maybe Text)
updateAgent_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAgent' {Maybe Text
name :: Maybe Text
$sel:name:UpdateAgent' :: UpdateAgent -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateAgent
s@UpdateAgent' {} Maybe Text
a -> UpdateAgent
s {$sel:name:UpdateAgent' :: Maybe Text
name = Maybe Text
a} :: UpdateAgent)

-- | The Amazon Resource Name (ARN) of the agent to update.
updateAgent_agentArn :: Lens.Lens' UpdateAgent Prelude.Text
updateAgent_agentArn :: Lens' UpdateAgent Text
updateAgent_agentArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAgent' {Text
agentArn :: Text
$sel:agentArn:UpdateAgent' :: UpdateAgent -> Text
agentArn} -> Text
agentArn) (\s :: UpdateAgent
s@UpdateAgent' {} Text
a -> UpdateAgent
s {$sel:agentArn:UpdateAgent' :: Text
agentArn = Text
a} :: UpdateAgent)

instance Core.AWSRequest UpdateAgent where
  type AWSResponse UpdateAgent = UpdateAgentResponse
  request :: (Service -> Service) -> UpdateAgent -> Request UpdateAgent
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 UpdateAgent
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateAgent)))
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 -> UpdateAgentResponse
UpdateAgentResponse'
            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 UpdateAgent where
  hashWithSalt :: Int -> UpdateAgent -> Int
hashWithSalt Int
_salt UpdateAgent' {Maybe Text
Text
agentArn :: Text
name :: Maybe Text
$sel:agentArn:UpdateAgent' :: UpdateAgent -> Text
$sel:name:UpdateAgent' :: UpdateAgent -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
agentArn

instance Prelude.NFData UpdateAgent where
  rnf :: UpdateAgent -> ()
rnf UpdateAgent' {Maybe Text
Text
agentArn :: Text
name :: Maybe Text
$sel:agentArn:UpdateAgent' :: UpdateAgent -> Text
$sel:name:UpdateAgent' :: UpdateAgent -> Maybe Text
..} =
    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 Text
agentArn

instance Data.ToHeaders UpdateAgent where
  toHeaders :: UpdateAgent -> 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
"FmrsService.UpdateAgent" :: 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 UpdateAgent where
  toJSON :: UpdateAgent -> Value
toJSON UpdateAgent' {Maybe Text
Text
agentArn :: Text
name :: Maybe Text
$sel:agentArn:UpdateAgent' :: UpdateAgent -> Text
$sel:name:UpdateAgent' :: UpdateAgent -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Name" 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
name,
            forall a. a -> Maybe a
Prelude.Just (Key
"AgentArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
agentArn)
          ]
      )

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

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

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

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

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

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