{-# 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 #-}
module Amazonka.DataExchange.UntagResource
(
UntagResource (..),
newUntagResource,
untagResource_resourceArn,
untagResource_tagKeys,
UntagResourceResponse (..),
newUntagResourceResponse,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataExchange.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data UntagResource = UntagResource'
{
UntagResource -> Text
resourceArn :: Prelude.Text,
UntagResource -> [Text]
tagKeys :: [Prelude.Text]
}
deriving (UntagResource -> UntagResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UntagResource -> UntagResource -> Bool
$c/= :: UntagResource -> UntagResource -> Bool
== :: UntagResource -> UntagResource -> Bool
$c== :: UntagResource -> UntagResource -> Bool
Prelude.Eq, ReadPrec [UntagResource]
ReadPrec UntagResource
Int -> ReadS UntagResource
ReadS [UntagResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UntagResource]
$creadListPrec :: ReadPrec [UntagResource]
readPrec :: ReadPrec UntagResource
$creadPrec :: ReadPrec UntagResource
readList :: ReadS [UntagResource]
$creadList :: ReadS [UntagResource]
readsPrec :: Int -> ReadS UntagResource
$creadsPrec :: Int -> ReadS UntagResource
Prelude.Read, Int -> UntagResource -> ShowS
[UntagResource] -> ShowS
UntagResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UntagResource] -> ShowS
$cshowList :: [UntagResource] -> ShowS
show :: UntagResource -> String
$cshow :: UntagResource -> String
showsPrec :: Int -> UntagResource -> ShowS
$cshowsPrec :: Int -> UntagResource -> ShowS
Prelude.Show, forall x. Rep UntagResource x -> UntagResource
forall x. UntagResource -> Rep UntagResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UntagResource x -> UntagResource
$cfrom :: forall x. UntagResource -> Rep UntagResource x
Prelude.Generic)
newUntagResource ::
Prelude.Text ->
UntagResource
newUntagResource :: Text -> UntagResource
newUntagResource Text
pResourceArn_ =
UntagResource'
{ $sel:resourceArn:UntagResource' :: Text
resourceArn = Text
pResourceArn_,
$sel:tagKeys:UntagResource' :: [Text]
tagKeys = forall a. Monoid a => a
Prelude.mempty
}
untagResource_resourceArn :: Lens.Lens' UntagResource Prelude.Text
untagResource_resourceArn :: Lens' UntagResource Text
untagResource_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagResource' {Text
resourceArn :: Text
$sel:resourceArn:UntagResource' :: UntagResource -> Text
resourceArn} -> Text
resourceArn) (\s :: UntagResource
s@UntagResource' {} Text
a -> UntagResource
s {$sel:resourceArn:UntagResource' :: Text
resourceArn = Text
a} :: UntagResource)
untagResource_tagKeys :: Lens.Lens' UntagResource [Prelude.Text]
untagResource_tagKeys :: Lens' UntagResource [Text]
untagResource_tagKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagResource' {[Text]
tagKeys :: [Text]
$sel:tagKeys:UntagResource' :: UntagResource -> [Text]
tagKeys} -> [Text]
tagKeys) (\s :: UntagResource
s@UntagResource' {} [Text]
a -> UntagResource
s {$sel:tagKeys:UntagResource' :: [Text]
tagKeys = [Text]
a} :: UntagResource) 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 UntagResource where
type
AWSResponse UntagResource =
UntagResourceResponse
request :: (Service -> Service) -> UntagResource -> Request UntagResource
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UntagResource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UntagResource)))
response =
forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UntagResourceResponse
UntagResourceResponse'
instance Prelude.Hashable UntagResource where
hashWithSalt :: Int -> UntagResource -> Int
hashWithSalt Int
_salt UntagResource' {[Text]
Text
tagKeys :: [Text]
resourceArn :: Text
$sel:tagKeys:UntagResource' :: UntagResource -> [Text]
$sel:resourceArn:UntagResource' :: UntagResource -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
tagKeys
instance Prelude.NFData UntagResource where
rnf :: UntagResource -> ()
rnf UntagResource' {[Text]
Text
tagKeys :: [Text]
resourceArn :: Text
$sel:tagKeys:UntagResource' :: UntagResource -> [Text]
$sel:resourceArn:UntagResource' :: UntagResource -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
tagKeys
instance Data.ToHeaders UntagResource where
toHeaders :: UntagResource -> [Header]
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 -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToPath UntagResource where
toPath :: UntagResource -> ByteString
toPath UntagResource' {[Text]
Text
tagKeys :: [Text]
resourceArn :: Text
$sel:tagKeys:UntagResource' :: UntagResource -> [Text]
$sel:resourceArn:UntagResource' :: UntagResource -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/tags/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
resourceArn]
instance Data.ToQuery UntagResource where
toQuery :: UntagResource -> QueryString
toQuery UntagResource' {[Text]
Text
tagKeys :: [Text]
resourceArn :: Text
$sel:tagKeys:UntagResource' :: UntagResource -> [Text]
$sel:resourceArn:UntagResource' :: UntagResource -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"tagKeys" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
tagKeys]
data UntagResourceResponse = UntagResourceResponse'
{
}
deriving (UntagResourceResponse -> UntagResourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UntagResourceResponse -> UntagResourceResponse -> Bool
$c/= :: UntagResourceResponse -> UntagResourceResponse -> Bool
== :: UntagResourceResponse -> UntagResourceResponse -> Bool
$c== :: UntagResourceResponse -> UntagResourceResponse -> Bool
Prelude.Eq, ReadPrec [UntagResourceResponse]
ReadPrec UntagResourceResponse
Int -> ReadS UntagResourceResponse
ReadS [UntagResourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UntagResourceResponse]
$creadListPrec :: ReadPrec [UntagResourceResponse]
readPrec :: ReadPrec UntagResourceResponse
$creadPrec :: ReadPrec UntagResourceResponse
readList :: ReadS [UntagResourceResponse]
$creadList :: ReadS [UntagResourceResponse]
readsPrec :: Int -> ReadS UntagResourceResponse
$creadsPrec :: Int -> ReadS UntagResourceResponse
Prelude.Read, Int -> UntagResourceResponse -> ShowS
[UntagResourceResponse] -> ShowS
UntagResourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UntagResourceResponse] -> ShowS
$cshowList :: [UntagResourceResponse] -> ShowS
show :: UntagResourceResponse -> String
$cshow :: UntagResourceResponse -> String
showsPrec :: Int -> UntagResourceResponse -> ShowS
$cshowsPrec :: Int -> UntagResourceResponse -> ShowS
Prelude.Show, forall x. Rep UntagResourceResponse x -> UntagResourceResponse
forall x. UntagResourceResponse -> Rep UntagResourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UntagResourceResponse x -> UntagResourceResponse
$cfrom :: forall x. UntagResourceResponse -> Rep UntagResourceResponse x
Prelude.Generic)
newUntagResourceResponse ::
UntagResourceResponse
newUntagResourceResponse :: UntagResourceResponse
newUntagResourceResponse = UntagResourceResponse
UntagResourceResponse'
instance Prelude.NFData UntagResourceResponse where
rnf :: UntagResourceResponse -> ()
rnf UntagResourceResponse
_ = ()