{-# 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.Discovery.DisassociateConfigurationItemsFromApplication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disassociates one or more configuration items from an application.
module Amazonka.Discovery.DisassociateConfigurationItemsFromApplication
  ( -- * Creating a Request
    DisassociateConfigurationItemsFromApplication (..),
    newDisassociateConfigurationItemsFromApplication,

    -- * Request Lenses
    disassociateConfigurationItemsFromApplication_applicationConfigurationId,
    disassociateConfigurationItemsFromApplication_configurationIds,

    -- * Destructuring the Response
    DisassociateConfigurationItemsFromApplicationResponse (..),
    newDisassociateConfigurationItemsFromApplicationResponse,

    -- * Response Lenses
    disassociateConfigurationItemsFromApplicationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDisassociateConfigurationItemsFromApplication' smart constructor.
data DisassociateConfigurationItemsFromApplication = DisassociateConfigurationItemsFromApplication'
  { -- | Configuration ID of an application from which each item is
    -- disassociated.
    DisassociateConfigurationItemsFromApplication -> Text
applicationConfigurationId :: Prelude.Text,
    -- | Configuration ID of each item to be disassociated from an application.
    DisassociateConfigurationItemsFromApplication -> [Text]
configurationIds :: [Prelude.Text]
  }
  deriving (DisassociateConfigurationItemsFromApplication
-> DisassociateConfigurationItemsFromApplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateConfigurationItemsFromApplication
-> DisassociateConfigurationItemsFromApplication -> Bool
$c/= :: DisassociateConfigurationItemsFromApplication
-> DisassociateConfigurationItemsFromApplication -> Bool
== :: DisassociateConfigurationItemsFromApplication
-> DisassociateConfigurationItemsFromApplication -> Bool
$c== :: DisassociateConfigurationItemsFromApplication
-> DisassociateConfigurationItemsFromApplication -> Bool
Prelude.Eq, ReadPrec [DisassociateConfigurationItemsFromApplication]
ReadPrec DisassociateConfigurationItemsFromApplication
Int -> ReadS DisassociateConfigurationItemsFromApplication
ReadS [DisassociateConfigurationItemsFromApplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateConfigurationItemsFromApplication]
$creadListPrec :: ReadPrec [DisassociateConfigurationItemsFromApplication]
readPrec :: ReadPrec DisassociateConfigurationItemsFromApplication
$creadPrec :: ReadPrec DisassociateConfigurationItemsFromApplication
readList :: ReadS [DisassociateConfigurationItemsFromApplication]
$creadList :: ReadS [DisassociateConfigurationItemsFromApplication]
readsPrec :: Int -> ReadS DisassociateConfigurationItemsFromApplication
$creadsPrec :: Int -> ReadS DisassociateConfigurationItemsFromApplication
Prelude.Read, Int -> DisassociateConfigurationItemsFromApplication -> ShowS
[DisassociateConfigurationItemsFromApplication] -> ShowS
DisassociateConfigurationItemsFromApplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateConfigurationItemsFromApplication] -> ShowS
$cshowList :: [DisassociateConfigurationItemsFromApplication] -> ShowS
show :: DisassociateConfigurationItemsFromApplication -> String
$cshow :: DisassociateConfigurationItemsFromApplication -> String
showsPrec :: Int -> DisassociateConfigurationItemsFromApplication -> ShowS
$cshowsPrec :: Int -> DisassociateConfigurationItemsFromApplication -> ShowS
Prelude.Show, forall x.
Rep DisassociateConfigurationItemsFromApplication x
-> DisassociateConfigurationItemsFromApplication
forall x.
DisassociateConfigurationItemsFromApplication
-> Rep DisassociateConfigurationItemsFromApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateConfigurationItemsFromApplication x
-> DisassociateConfigurationItemsFromApplication
$cfrom :: forall x.
DisassociateConfigurationItemsFromApplication
-> Rep DisassociateConfigurationItemsFromApplication x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateConfigurationItemsFromApplication' 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:
--
-- 'applicationConfigurationId', 'disassociateConfigurationItemsFromApplication_applicationConfigurationId' - Configuration ID of an application from which each item is
-- disassociated.
--
-- 'configurationIds', 'disassociateConfigurationItemsFromApplication_configurationIds' - Configuration ID of each item to be disassociated from an application.
newDisassociateConfigurationItemsFromApplication ::
  -- | 'applicationConfigurationId'
  Prelude.Text ->
  DisassociateConfigurationItemsFromApplication
newDisassociateConfigurationItemsFromApplication :: Text -> DisassociateConfigurationItemsFromApplication
newDisassociateConfigurationItemsFromApplication
  Text
pApplicationConfigurationId_ =
    DisassociateConfigurationItemsFromApplication'
      { $sel:applicationConfigurationId:DisassociateConfigurationItemsFromApplication' :: Text
applicationConfigurationId =
          Text
pApplicationConfigurationId_,
        $sel:configurationIds:DisassociateConfigurationItemsFromApplication' :: [Text]
configurationIds =
          forall a. Monoid a => a
Prelude.mempty
      }

-- | Configuration ID of an application from which each item is
-- disassociated.
disassociateConfigurationItemsFromApplication_applicationConfigurationId :: Lens.Lens' DisassociateConfigurationItemsFromApplication Prelude.Text
disassociateConfigurationItemsFromApplication_applicationConfigurationId :: Lens' DisassociateConfigurationItemsFromApplication Text
disassociateConfigurationItemsFromApplication_applicationConfigurationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateConfigurationItemsFromApplication' {Text
applicationConfigurationId :: Text
$sel:applicationConfigurationId:DisassociateConfigurationItemsFromApplication' :: DisassociateConfigurationItemsFromApplication -> Text
applicationConfigurationId} -> Text
applicationConfigurationId) (\s :: DisassociateConfigurationItemsFromApplication
s@DisassociateConfigurationItemsFromApplication' {} Text
a -> DisassociateConfigurationItemsFromApplication
s {$sel:applicationConfigurationId:DisassociateConfigurationItemsFromApplication' :: Text
applicationConfigurationId = Text
a} :: DisassociateConfigurationItemsFromApplication)

-- | Configuration ID of each item to be disassociated from an application.
disassociateConfigurationItemsFromApplication_configurationIds :: Lens.Lens' DisassociateConfigurationItemsFromApplication [Prelude.Text]
disassociateConfigurationItemsFromApplication_configurationIds :: Lens' DisassociateConfigurationItemsFromApplication [Text]
disassociateConfigurationItemsFromApplication_configurationIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateConfigurationItemsFromApplication' {[Text]
configurationIds :: [Text]
$sel:configurationIds:DisassociateConfigurationItemsFromApplication' :: DisassociateConfigurationItemsFromApplication -> [Text]
configurationIds} -> [Text]
configurationIds) (\s :: DisassociateConfigurationItemsFromApplication
s@DisassociateConfigurationItemsFromApplication' {} [Text]
a -> DisassociateConfigurationItemsFromApplication
s {$sel:configurationIds:DisassociateConfigurationItemsFromApplication' :: [Text]
configurationIds = [Text]
a} :: DisassociateConfigurationItemsFromApplication) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Core.AWSRequest
    DisassociateConfigurationItemsFromApplication
  where
  type
    AWSResponse
      DisassociateConfigurationItemsFromApplication =
      DisassociateConfigurationItemsFromApplicationResponse
  request :: (Service -> Service)
-> DisassociateConfigurationItemsFromApplication
-> Request DisassociateConfigurationItemsFromApplication
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 DisassociateConfigurationItemsFromApplication
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DisassociateConfigurationItemsFromApplication)))
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 -> DisassociateConfigurationItemsFromApplicationResponse
DisassociateConfigurationItemsFromApplicationResponse'
            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
    DisassociateConfigurationItemsFromApplication
  where
  hashWithSalt :: Int -> DisassociateConfigurationItemsFromApplication -> Int
hashWithSalt
    Int
_salt
    DisassociateConfigurationItemsFromApplication' {[Text]
Text
configurationIds :: [Text]
applicationConfigurationId :: Text
$sel:configurationIds:DisassociateConfigurationItemsFromApplication' :: DisassociateConfigurationItemsFromApplication -> [Text]
$sel:applicationConfigurationId:DisassociateConfigurationItemsFromApplication' :: DisassociateConfigurationItemsFromApplication -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationConfigurationId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
configurationIds

instance
  Prelude.NFData
    DisassociateConfigurationItemsFromApplication
  where
  rnf :: DisassociateConfigurationItemsFromApplication -> ()
rnf
    DisassociateConfigurationItemsFromApplication' {[Text]
Text
configurationIds :: [Text]
applicationConfigurationId :: Text
$sel:configurationIds:DisassociateConfigurationItemsFromApplication' :: DisassociateConfigurationItemsFromApplication -> [Text]
$sel:applicationConfigurationId:DisassociateConfigurationItemsFromApplication' :: DisassociateConfigurationItemsFromApplication -> Text
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Text
applicationConfigurationId
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
configurationIds

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

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

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

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

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

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

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