{-# 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.DeleteTags
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the association between configuration items and one or more
-- tags. This API accepts a list of multiple configuration items.
module Amazonka.Discovery.DeleteTags
  ( -- * Creating a Request
    DeleteTags (..),
    newDeleteTags,

    -- * Request Lenses
    deleteTags_tags,
    deleteTags_configurationIds,

    -- * Destructuring the Response
    DeleteTagsResponse (..),
    newDeleteTagsResponse,

    -- * Response Lenses
    deleteTagsResponse_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:/ 'newDeleteTags' smart constructor.
data DeleteTags = DeleteTags'
  { -- | Tags that you want to delete from one or more configuration items.
    -- Specify the tags that you want to delete in a /key/-/value/ format. For
    -- example:
    --
    -- @{\"key\": \"serverType\", \"value\": \"webServer\"}@
    DeleteTags -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A list of configuration items with tags that you want to delete.
    DeleteTags -> [Text]
configurationIds :: [Prelude.Text]
  }
  deriving (DeleteTags -> DeleteTags -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteTags -> DeleteTags -> Bool
$c/= :: DeleteTags -> DeleteTags -> Bool
== :: DeleteTags -> DeleteTags -> Bool
$c== :: DeleteTags -> DeleteTags -> Bool
Prelude.Eq, ReadPrec [DeleteTags]
ReadPrec DeleteTags
Int -> ReadS DeleteTags
ReadS [DeleteTags]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteTags]
$creadListPrec :: ReadPrec [DeleteTags]
readPrec :: ReadPrec DeleteTags
$creadPrec :: ReadPrec DeleteTags
readList :: ReadS [DeleteTags]
$creadList :: ReadS [DeleteTags]
readsPrec :: Int -> ReadS DeleteTags
$creadsPrec :: Int -> ReadS DeleteTags
Prelude.Read, Int -> DeleteTags -> ShowS
[DeleteTags] -> ShowS
DeleteTags -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteTags] -> ShowS
$cshowList :: [DeleteTags] -> ShowS
show :: DeleteTags -> String
$cshow :: DeleteTags -> String
showsPrec :: Int -> DeleteTags -> ShowS
$cshowsPrec :: Int -> DeleteTags -> ShowS
Prelude.Show, forall x. Rep DeleteTags x -> DeleteTags
forall x. DeleteTags -> Rep DeleteTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteTags x -> DeleteTags
$cfrom :: forall x. DeleteTags -> Rep DeleteTags x
Prelude.Generic)

-- |
-- Create a value of 'DeleteTags' 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:
--
-- 'tags', 'deleteTags_tags' - Tags that you want to delete from one or more configuration items.
-- Specify the tags that you want to delete in a /key/-/value/ format. For
-- example:
--
-- @{\"key\": \"serverType\", \"value\": \"webServer\"}@
--
-- 'configurationIds', 'deleteTags_configurationIds' - A list of configuration items with tags that you want to delete.
newDeleteTags ::
  DeleteTags
newDeleteTags :: DeleteTags
newDeleteTags =
  DeleteTags'
    { $sel:tags:DeleteTags' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationIds:DeleteTags' :: [Text]
configurationIds = forall a. Monoid a => a
Prelude.mempty
    }

-- | Tags that you want to delete from one or more configuration items.
-- Specify the tags that you want to delete in a /key/-/value/ format. For
-- example:
--
-- @{\"key\": \"serverType\", \"value\": \"webServer\"}@
deleteTags_tags :: Lens.Lens' DeleteTags (Prelude.Maybe [Tag])
deleteTags_tags :: Lens' DeleteTags (Maybe [Tag])
deleteTags_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTags' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:DeleteTags' :: DeleteTags -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: DeleteTags
s@DeleteTags' {} Maybe [Tag]
a -> DeleteTags
s {$sel:tags:DeleteTags' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: DeleteTags) 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

-- | A list of configuration items with tags that you want to delete.
deleteTags_configurationIds :: Lens.Lens' DeleteTags [Prelude.Text]
deleteTags_configurationIds :: Lens' DeleteTags [Text]
deleteTags_configurationIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTags' {[Text]
configurationIds :: [Text]
$sel:configurationIds:DeleteTags' :: DeleteTags -> [Text]
configurationIds} -> [Text]
configurationIds) (\s :: DeleteTags
s@DeleteTags' {} [Text]
a -> DeleteTags
s {$sel:configurationIds:DeleteTags' :: [Text]
configurationIds = [Text]
a} :: DeleteTags) 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 DeleteTags where
  type AWSResponse DeleteTags = DeleteTagsResponse
  request :: (Service -> Service) -> DeleteTags -> Request DeleteTags
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 DeleteTags
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteTags)))
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 -> DeleteTagsResponse
DeleteTagsResponse'
            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 DeleteTags where
  hashWithSalt :: Int -> DeleteTags -> Int
hashWithSalt Int
_salt DeleteTags' {[Text]
Maybe [Tag]
configurationIds :: [Text]
tags :: Maybe [Tag]
$sel:configurationIds:DeleteTags' :: DeleteTags -> [Text]
$sel:tags:DeleteTags' :: DeleteTags -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
configurationIds

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

instance Data.ToHeaders DeleteTags where
  toHeaders :: DeleteTags -> 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.DeleteTags" ::
                          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 DeleteTags where
  toJSON :: DeleteTags -> Value
toJSON DeleteTags' {[Text]
Maybe [Tag]
configurationIds :: [Text]
tags :: Maybe [Tag]
$sel:configurationIds:DeleteTags' :: DeleteTags -> [Text]
$sel:tags:DeleteTags' :: DeleteTags -> Maybe [Tag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"tags" 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 [Tag]
tags,
            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 DeleteTags where
  toPath :: DeleteTags -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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