{-# 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.ECS.DeleteAttributes
-- 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 one or more custom attributes from an Amazon ECS resource.
module Amazonka.ECS.DeleteAttributes
  ( -- * Creating a Request
    DeleteAttributes (..),
    newDeleteAttributes,

    -- * Request Lenses
    deleteAttributes_cluster,
    deleteAttributes_attributes,

    -- * Destructuring the Response
    DeleteAttributesResponse (..),
    newDeleteAttributesResponse,

    -- * Response Lenses
    deleteAttributesResponse_attributes,
    deleteAttributesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteAttributes' smart constructor.
data DeleteAttributes = DeleteAttributes'
  { -- | The short name or full Amazon Resource Name (ARN) of the cluster that
    -- contains the resource to delete attributes. If you do not specify a
    -- cluster, the default cluster is assumed.
    DeleteAttributes -> Maybe Text
cluster :: Prelude.Maybe Prelude.Text,
    -- | The attributes to delete from your resource. You can specify up to 10
    -- attributes for each request. For custom attributes, specify the
    -- attribute name and target ID, but don\'t specify the value. If you
    -- specify the target ID using the short form, you must also specify the
    -- target type.
    DeleteAttributes -> [Attribute]
attributes :: [Attribute]
  }
  deriving (DeleteAttributes -> DeleteAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAttributes -> DeleteAttributes -> Bool
$c/= :: DeleteAttributes -> DeleteAttributes -> Bool
== :: DeleteAttributes -> DeleteAttributes -> Bool
$c== :: DeleteAttributes -> DeleteAttributes -> Bool
Prelude.Eq, ReadPrec [DeleteAttributes]
ReadPrec DeleteAttributes
Int -> ReadS DeleteAttributes
ReadS [DeleteAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAttributes]
$creadListPrec :: ReadPrec [DeleteAttributes]
readPrec :: ReadPrec DeleteAttributes
$creadPrec :: ReadPrec DeleteAttributes
readList :: ReadS [DeleteAttributes]
$creadList :: ReadS [DeleteAttributes]
readsPrec :: Int -> ReadS DeleteAttributes
$creadsPrec :: Int -> ReadS DeleteAttributes
Prelude.Read, Int -> DeleteAttributes -> ShowS
[DeleteAttributes] -> ShowS
DeleteAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAttributes] -> ShowS
$cshowList :: [DeleteAttributes] -> ShowS
show :: DeleteAttributes -> String
$cshow :: DeleteAttributes -> String
showsPrec :: Int -> DeleteAttributes -> ShowS
$cshowsPrec :: Int -> DeleteAttributes -> ShowS
Prelude.Show, forall x. Rep DeleteAttributes x -> DeleteAttributes
forall x. DeleteAttributes -> Rep DeleteAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAttributes x -> DeleteAttributes
$cfrom :: forall x. DeleteAttributes -> Rep DeleteAttributes x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAttributes' 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:
--
-- 'cluster', 'deleteAttributes_cluster' - The short name or full Amazon Resource Name (ARN) of the cluster that
-- contains the resource to delete attributes. If you do not specify a
-- cluster, the default cluster is assumed.
--
-- 'attributes', 'deleteAttributes_attributes' - The attributes to delete from your resource. You can specify up to 10
-- attributes for each request. For custom attributes, specify the
-- attribute name and target ID, but don\'t specify the value. If you
-- specify the target ID using the short form, you must also specify the
-- target type.
newDeleteAttributes ::
  DeleteAttributes
newDeleteAttributes :: DeleteAttributes
newDeleteAttributes =
  DeleteAttributes'
    { $sel:cluster:DeleteAttributes' :: Maybe Text
cluster = forall a. Maybe a
Prelude.Nothing,
      $sel:attributes:DeleteAttributes' :: [Attribute]
attributes = forall a. Monoid a => a
Prelude.mempty
    }

-- | The short name or full Amazon Resource Name (ARN) of the cluster that
-- contains the resource to delete attributes. If you do not specify a
-- cluster, the default cluster is assumed.
deleteAttributes_cluster :: Lens.Lens' DeleteAttributes (Prelude.Maybe Prelude.Text)
deleteAttributes_cluster :: Lens' DeleteAttributes (Maybe Text)
deleteAttributes_cluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAttributes' {Maybe Text
cluster :: Maybe Text
$sel:cluster:DeleteAttributes' :: DeleteAttributes -> Maybe Text
cluster} -> Maybe Text
cluster) (\s :: DeleteAttributes
s@DeleteAttributes' {} Maybe Text
a -> DeleteAttributes
s {$sel:cluster:DeleteAttributes' :: Maybe Text
cluster = Maybe Text
a} :: DeleteAttributes)

-- | The attributes to delete from your resource. You can specify up to 10
-- attributes for each request. For custom attributes, specify the
-- attribute name and target ID, but don\'t specify the value. If you
-- specify the target ID using the short form, you must also specify the
-- target type.
deleteAttributes_attributes :: Lens.Lens' DeleteAttributes [Attribute]
deleteAttributes_attributes :: Lens' DeleteAttributes [Attribute]
deleteAttributes_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAttributes' {[Attribute]
attributes :: [Attribute]
$sel:attributes:DeleteAttributes' :: DeleteAttributes -> [Attribute]
attributes} -> [Attribute]
attributes) (\s :: DeleteAttributes
s@DeleteAttributes' {} [Attribute]
a -> DeleteAttributes
s {$sel:attributes:DeleteAttributes' :: [Attribute]
attributes = [Attribute]
a} :: DeleteAttributes) 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 DeleteAttributes where
  type
    AWSResponse DeleteAttributes =
      DeleteAttributesResponse
  request :: (Service -> Service)
-> DeleteAttributes -> Request DeleteAttributes
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 DeleteAttributes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteAttributes)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [Attribute] -> Int -> DeleteAttributesResponse
DeleteAttributesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"attributes" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => 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 DeleteAttributes where
  hashWithSalt :: Int -> DeleteAttributes -> Int
hashWithSalt Int
_salt DeleteAttributes' {[Attribute]
Maybe Text
attributes :: [Attribute]
cluster :: Maybe Text
$sel:attributes:DeleteAttributes' :: DeleteAttributes -> [Attribute]
$sel:cluster:DeleteAttributes' :: DeleteAttributes -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cluster
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Attribute]
attributes

instance Prelude.NFData DeleteAttributes where
  rnf :: DeleteAttributes -> ()
rnf DeleteAttributes' {[Attribute]
Maybe Text
attributes :: [Attribute]
cluster :: Maybe Text
$sel:attributes:DeleteAttributes' :: DeleteAttributes -> [Attribute]
$sel:cluster:DeleteAttributes' :: DeleteAttributes -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cluster
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Attribute]
attributes

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

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

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

-- | /See:/ 'newDeleteAttributesResponse' smart constructor.
data DeleteAttributesResponse = DeleteAttributesResponse'
  { -- | A list of attribute objects that were successfully deleted from your
    -- resource.
    DeleteAttributesResponse -> Maybe [Attribute]
attributes :: Prelude.Maybe [Attribute],
    -- | The response's http status code.
    DeleteAttributesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteAttributesResponse -> DeleteAttributesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAttributesResponse -> DeleteAttributesResponse -> Bool
$c/= :: DeleteAttributesResponse -> DeleteAttributesResponse -> Bool
== :: DeleteAttributesResponse -> DeleteAttributesResponse -> Bool
$c== :: DeleteAttributesResponse -> DeleteAttributesResponse -> Bool
Prelude.Eq, ReadPrec [DeleteAttributesResponse]
ReadPrec DeleteAttributesResponse
Int -> ReadS DeleteAttributesResponse
ReadS [DeleteAttributesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAttributesResponse]
$creadListPrec :: ReadPrec [DeleteAttributesResponse]
readPrec :: ReadPrec DeleteAttributesResponse
$creadPrec :: ReadPrec DeleteAttributesResponse
readList :: ReadS [DeleteAttributesResponse]
$creadList :: ReadS [DeleteAttributesResponse]
readsPrec :: Int -> ReadS DeleteAttributesResponse
$creadsPrec :: Int -> ReadS DeleteAttributesResponse
Prelude.Read, Int -> DeleteAttributesResponse -> ShowS
[DeleteAttributesResponse] -> ShowS
DeleteAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAttributesResponse] -> ShowS
$cshowList :: [DeleteAttributesResponse] -> ShowS
show :: DeleteAttributesResponse -> String
$cshow :: DeleteAttributesResponse -> String
showsPrec :: Int -> DeleteAttributesResponse -> ShowS
$cshowsPrec :: Int -> DeleteAttributesResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteAttributesResponse x -> DeleteAttributesResponse
forall x.
DeleteAttributesResponse -> Rep DeleteAttributesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAttributesResponse x -> DeleteAttributesResponse
$cfrom :: forall x.
DeleteAttributesResponse -> Rep DeleteAttributesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAttributesResponse' 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:
--
-- 'attributes', 'deleteAttributesResponse_attributes' - A list of attribute objects that were successfully deleted from your
-- resource.
--
-- 'httpStatus', 'deleteAttributesResponse_httpStatus' - The response's http status code.
newDeleteAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteAttributesResponse
newDeleteAttributesResponse :: Int -> DeleteAttributesResponse
newDeleteAttributesResponse Int
pHttpStatus_ =
  DeleteAttributesResponse'
    { $sel:attributes:DeleteAttributesResponse' :: Maybe [Attribute]
attributes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of attribute objects that were successfully deleted from your
-- resource.
deleteAttributesResponse_attributes :: Lens.Lens' DeleteAttributesResponse (Prelude.Maybe [Attribute])
deleteAttributesResponse_attributes :: Lens' DeleteAttributesResponse (Maybe [Attribute])
deleteAttributesResponse_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAttributesResponse' {Maybe [Attribute]
attributes :: Maybe [Attribute]
$sel:attributes:DeleteAttributesResponse' :: DeleteAttributesResponse -> Maybe [Attribute]
attributes} -> Maybe [Attribute]
attributes) (\s :: DeleteAttributesResponse
s@DeleteAttributesResponse' {} Maybe [Attribute]
a -> DeleteAttributesResponse
s {$sel:attributes:DeleteAttributesResponse' :: Maybe [Attribute]
attributes = Maybe [Attribute]
a} :: DeleteAttributesResponse) 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 response's http status code.
deleteAttributesResponse_httpStatus :: Lens.Lens' DeleteAttributesResponse Prelude.Int
deleteAttributesResponse_httpStatus :: Lens' DeleteAttributesResponse Int
deleteAttributesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAttributesResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteAttributesResponse' :: DeleteAttributesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteAttributesResponse
s@DeleteAttributesResponse' {} Int
a -> DeleteAttributesResponse
s {$sel:httpStatus:DeleteAttributesResponse' :: Int
httpStatus = Int
a} :: DeleteAttributesResponse)

instance Prelude.NFData DeleteAttributesResponse where
  rnf :: DeleteAttributesResponse -> ()
rnf DeleteAttributesResponse' {Int
Maybe [Attribute]
httpStatus :: Int
attributes :: Maybe [Attribute]
$sel:httpStatus:DeleteAttributesResponse' :: DeleteAttributesResponse -> Int
$sel:attributes:DeleteAttributesResponse' :: DeleteAttributesResponse -> Maybe [Attribute]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Attribute]
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus