{-# 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.AppIntegrationS.UpdateDataIntegration
-- 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 description of a DataIntegration.
--
-- You cannot create a DataIntegration association for a DataIntegration
-- that has been previously associated. Use a different DataIntegration, or
-- recreate the DataIntegration using the
-- <https://docs.aws.amazon.com/appintegrations/latest/APIReference/API_CreateDataIntegration.html CreateDataIntegration>
-- API.
module Amazonka.AppIntegrationS.UpdateDataIntegration
  ( -- * Creating a Request
    UpdateDataIntegration (..),
    newUpdateDataIntegration,

    -- * Request Lenses
    updateDataIntegration_description,
    updateDataIntegration_name,
    updateDataIntegration_identifier,

    -- * Destructuring the Response
    UpdateDataIntegrationResponse (..),
    newUpdateDataIntegrationResponse,

    -- * Response Lenses
    updateDataIntegrationResponse_httpStatus,
  )
where

import Amazonka.AppIntegrationS.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:/ 'newUpdateDataIntegration' smart constructor.
data UpdateDataIntegration = UpdateDataIntegration'
  { -- | A description of the DataIntegration.
    UpdateDataIntegration -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The name of the DataIntegration.
    UpdateDataIntegration -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the DataIntegration.
    UpdateDataIntegration -> Text
identifier :: Prelude.Text
  }
  deriving (UpdateDataIntegration -> UpdateDataIntegration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDataIntegration -> UpdateDataIntegration -> Bool
$c/= :: UpdateDataIntegration -> UpdateDataIntegration -> Bool
== :: UpdateDataIntegration -> UpdateDataIntegration -> Bool
$c== :: UpdateDataIntegration -> UpdateDataIntegration -> Bool
Prelude.Eq, ReadPrec [UpdateDataIntegration]
ReadPrec UpdateDataIntegration
Int -> ReadS UpdateDataIntegration
ReadS [UpdateDataIntegration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDataIntegration]
$creadListPrec :: ReadPrec [UpdateDataIntegration]
readPrec :: ReadPrec UpdateDataIntegration
$creadPrec :: ReadPrec UpdateDataIntegration
readList :: ReadS [UpdateDataIntegration]
$creadList :: ReadS [UpdateDataIntegration]
readsPrec :: Int -> ReadS UpdateDataIntegration
$creadsPrec :: Int -> ReadS UpdateDataIntegration
Prelude.Read, Int -> UpdateDataIntegration -> ShowS
[UpdateDataIntegration] -> ShowS
UpdateDataIntegration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDataIntegration] -> ShowS
$cshowList :: [UpdateDataIntegration] -> ShowS
show :: UpdateDataIntegration -> String
$cshow :: UpdateDataIntegration -> String
showsPrec :: Int -> UpdateDataIntegration -> ShowS
$cshowsPrec :: Int -> UpdateDataIntegration -> ShowS
Prelude.Show, forall x. Rep UpdateDataIntegration x -> UpdateDataIntegration
forall x. UpdateDataIntegration -> Rep UpdateDataIntegration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateDataIntegration x -> UpdateDataIntegration
$cfrom :: forall x. UpdateDataIntegration -> Rep UpdateDataIntegration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDataIntegration' 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', 'updateDataIntegration_description' - A description of the DataIntegration.
--
-- 'name', 'updateDataIntegration_name' - The name of the DataIntegration.
--
-- 'identifier', 'updateDataIntegration_identifier' - A unique identifier for the DataIntegration.
newUpdateDataIntegration ::
  -- | 'identifier'
  Prelude.Text ->
  UpdateDataIntegration
newUpdateDataIntegration :: Text -> UpdateDataIntegration
newUpdateDataIntegration Text
pIdentifier_ =
  UpdateDataIntegration'
    { $sel:description:UpdateDataIntegration' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateDataIntegration' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:identifier:UpdateDataIntegration' :: Text
identifier = Text
pIdentifier_
    }

-- | A description of the DataIntegration.
updateDataIntegration_description :: Lens.Lens' UpdateDataIntegration (Prelude.Maybe Prelude.Text)
updateDataIntegration_description :: Lens' UpdateDataIntegration (Maybe Text)
updateDataIntegration_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDataIntegration' {Maybe Text
description :: Maybe Text
$sel:description:UpdateDataIntegration' :: UpdateDataIntegration -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateDataIntegration
s@UpdateDataIntegration' {} Maybe Text
a -> UpdateDataIntegration
s {$sel:description:UpdateDataIntegration' :: Maybe Text
description = Maybe Text
a} :: UpdateDataIntegration)

-- | The name of the DataIntegration.
updateDataIntegration_name :: Lens.Lens' UpdateDataIntegration (Prelude.Maybe Prelude.Text)
updateDataIntegration_name :: Lens' UpdateDataIntegration (Maybe Text)
updateDataIntegration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDataIntegration' {Maybe Text
name :: Maybe Text
$sel:name:UpdateDataIntegration' :: UpdateDataIntegration -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateDataIntegration
s@UpdateDataIntegration' {} Maybe Text
a -> UpdateDataIntegration
s {$sel:name:UpdateDataIntegration' :: Maybe Text
name = Maybe Text
a} :: UpdateDataIntegration)

-- | A unique identifier for the DataIntegration.
updateDataIntegration_identifier :: Lens.Lens' UpdateDataIntegration Prelude.Text
updateDataIntegration_identifier :: Lens' UpdateDataIntegration Text
updateDataIntegration_identifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDataIntegration' {Text
identifier :: Text
$sel:identifier:UpdateDataIntegration' :: UpdateDataIntegration -> Text
identifier} -> Text
identifier) (\s :: UpdateDataIntegration
s@UpdateDataIntegration' {} Text
a -> UpdateDataIntegration
s {$sel:identifier:UpdateDataIntegration' :: Text
identifier = Text
a} :: UpdateDataIntegration)

instance Core.AWSRequest UpdateDataIntegration where
  type
    AWSResponse UpdateDataIntegration =
      UpdateDataIntegrationResponse
  request :: (Service -> Service)
-> UpdateDataIntegration -> Request UpdateDataIntegration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateDataIntegration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateDataIntegration)))
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 -> UpdateDataIntegrationResponse
UpdateDataIntegrationResponse'
            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 UpdateDataIntegration where
  hashWithSalt :: Int -> UpdateDataIntegration -> Int
hashWithSalt Int
_salt UpdateDataIntegration' {Maybe Text
Text
identifier :: Text
name :: Maybe Text
description :: Maybe Text
$sel:identifier:UpdateDataIntegration' :: UpdateDataIntegration -> Text
$sel:name:UpdateDataIntegration' :: UpdateDataIntegration -> Maybe Text
$sel:description:UpdateDataIntegration' :: UpdateDataIntegration -> 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 Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identifier

instance Prelude.NFData UpdateDataIntegration where
  rnf :: UpdateDataIntegration -> ()
rnf UpdateDataIntegration' {Maybe Text
Text
identifier :: Text
name :: Maybe Text
description :: Maybe Text
$sel:identifier:UpdateDataIntegration' :: UpdateDataIntegration -> Text
$sel:name:UpdateDataIntegration' :: UpdateDataIntegration -> Maybe Text
$sel:description:UpdateDataIntegration' :: UpdateDataIntegration -> 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 Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
identifier

instance Data.ToHeaders UpdateDataIntegration where
  toHeaders :: UpdateDataIntegration -> 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 UpdateDataIntegration where
  toJSON :: UpdateDataIntegration -> Value
toJSON UpdateDataIntegration' {Maybe Text
Text
identifier :: Text
name :: Maybe Text
description :: Maybe Text
$sel:identifier:UpdateDataIntegration' :: UpdateDataIntegration -> Text
$sel:name:UpdateDataIntegration' :: UpdateDataIntegration -> Maybe Text
$sel:description:UpdateDataIntegration' :: UpdateDataIntegration -> 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
"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
          ]
      )

instance Data.ToPath UpdateDataIntegration where
  toPath :: UpdateDataIntegration -> ByteString
toPath UpdateDataIntegration' {Maybe Text
Text
identifier :: Text
name :: Maybe Text
description :: Maybe Text
$sel:identifier:UpdateDataIntegration' :: UpdateDataIntegration -> Text
$sel:name:UpdateDataIntegration' :: UpdateDataIntegration -> Maybe Text
$sel:description:UpdateDataIntegration' :: UpdateDataIntegration -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/dataIntegrations/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
identifier]

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

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

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

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

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