{-# 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.SSM.AddTagsToResource
(
AddTagsToResource (..),
newAddTagsToResource,
addTagsToResource_resourceType,
addTagsToResource_resourceId,
addTagsToResource_tags,
AddTagsToResourceResponse (..),
newAddTagsToResourceResponse,
addTagsToResourceResponse_httpStatus,
)
where
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
import Amazonka.SSM.Types
data AddTagsToResource = AddTagsToResource'
{
AddTagsToResource -> ResourceTypeForTagging
resourceType :: ResourceTypeForTagging,
AddTagsToResource -> Text
resourceId :: Prelude.Text,
AddTagsToResource -> [Tag]
tags :: [Tag]
}
deriving (AddTagsToResource -> AddTagsToResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddTagsToResource -> AddTagsToResource -> Bool
$c/= :: AddTagsToResource -> AddTagsToResource -> Bool
== :: AddTagsToResource -> AddTagsToResource -> Bool
$c== :: AddTagsToResource -> AddTagsToResource -> Bool
Prelude.Eq, ReadPrec [AddTagsToResource]
ReadPrec AddTagsToResource
Int -> ReadS AddTagsToResource
ReadS [AddTagsToResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddTagsToResource]
$creadListPrec :: ReadPrec [AddTagsToResource]
readPrec :: ReadPrec AddTagsToResource
$creadPrec :: ReadPrec AddTagsToResource
readList :: ReadS [AddTagsToResource]
$creadList :: ReadS [AddTagsToResource]
readsPrec :: Int -> ReadS AddTagsToResource
$creadsPrec :: Int -> ReadS AddTagsToResource
Prelude.Read, Int -> AddTagsToResource -> ShowS
[AddTagsToResource] -> ShowS
AddTagsToResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddTagsToResource] -> ShowS
$cshowList :: [AddTagsToResource] -> ShowS
show :: AddTagsToResource -> String
$cshow :: AddTagsToResource -> String
showsPrec :: Int -> AddTagsToResource -> ShowS
$cshowsPrec :: Int -> AddTagsToResource -> ShowS
Prelude.Show, forall x. Rep AddTagsToResource x -> AddTagsToResource
forall x. AddTagsToResource -> Rep AddTagsToResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddTagsToResource x -> AddTagsToResource
$cfrom :: forall x. AddTagsToResource -> Rep AddTagsToResource x
Prelude.Generic)
newAddTagsToResource ::
ResourceTypeForTagging ->
Prelude.Text ->
AddTagsToResource
newAddTagsToResource :: ResourceTypeForTagging -> Text -> AddTagsToResource
newAddTagsToResource ResourceTypeForTagging
pResourceType_ Text
pResourceId_ =
AddTagsToResource'
{ $sel:resourceType:AddTagsToResource' :: ResourceTypeForTagging
resourceType = ResourceTypeForTagging
pResourceType_,
$sel:resourceId:AddTagsToResource' :: Text
resourceId = Text
pResourceId_,
$sel:tags:AddTagsToResource' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
}
addTagsToResource_resourceType :: Lens.Lens' AddTagsToResource ResourceTypeForTagging
addTagsToResource_resourceType :: Lens' AddTagsToResource ResourceTypeForTagging
addTagsToResource_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddTagsToResource' {ResourceTypeForTagging
resourceType :: ResourceTypeForTagging
$sel:resourceType:AddTagsToResource' :: AddTagsToResource -> ResourceTypeForTagging
resourceType} -> ResourceTypeForTagging
resourceType) (\s :: AddTagsToResource
s@AddTagsToResource' {} ResourceTypeForTagging
a -> AddTagsToResource
s {$sel:resourceType:AddTagsToResource' :: ResourceTypeForTagging
resourceType = ResourceTypeForTagging
a} :: AddTagsToResource)
addTagsToResource_resourceId :: Lens.Lens' AddTagsToResource Prelude.Text
addTagsToResource_resourceId :: Lens' AddTagsToResource Text
addTagsToResource_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddTagsToResource' {Text
resourceId :: Text
$sel:resourceId:AddTagsToResource' :: AddTagsToResource -> Text
resourceId} -> Text
resourceId) (\s :: AddTagsToResource
s@AddTagsToResource' {} Text
a -> AddTagsToResource
s {$sel:resourceId:AddTagsToResource' :: Text
resourceId = Text
a} :: AddTagsToResource)
addTagsToResource_tags :: Lens.Lens' AddTagsToResource [Tag]
addTagsToResource_tags :: Lens' AddTagsToResource [Tag]
addTagsToResource_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddTagsToResource' {[Tag]
tags :: [Tag]
$sel:tags:AddTagsToResource' :: AddTagsToResource -> [Tag]
tags} -> [Tag]
tags) (\s :: AddTagsToResource
s@AddTagsToResource' {} [Tag]
a -> AddTagsToResource
s {$sel:tags:AddTagsToResource' :: [Tag]
tags = [Tag]
a} :: AddTagsToResource) 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 AddTagsToResource where
type
AWSResponse AddTagsToResource =
AddTagsToResourceResponse
request :: (Service -> Service)
-> AddTagsToResource -> Request AddTagsToResource
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 AddTagsToResource
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse AddTagsToResource)))
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 -> AddTagsToResourceResponse
AddTagsToResourceResponse'
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 AddTagsToResource where
hashWithSalt :: Int -> AddTagsToResource -> Int
hashWithSalt Int
_salt AddTagsToResource' {[Tag]
Text
ResourceTypeForTagging
tags :: [Tag]
resourceId :: Text
resourceType :: ResourceTypeForTagging
$sel:tags:AddTagsToResource' :: AddTagsToResource -> [Tag]
$sel:resourceId:AddTagsToResource' :: AddTagsToResource -> Text
$sel:resourceType:AddTagsToResource' :: AddTagsToResource -> ResourceTypeForTagging
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ResourceTypeForTagging
resourceType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Tag]
tags
instance Prelude.NFData AddTagsToResource where
rnf :: AddTagsToResource -> ()
rnf AddTagsToResource' {[Tag]
Text
ResourceTypeForTagging
tags :: [Tag]
resourceId :: Text
resourceType :: ResourceTypeForTagging
$sel:tags:AddTagsToResource' :: AddTagsToResource -> [Tag]
$sel:resourceId:AddTagsToResource' :: AddTagsToResource -> Text
$sel:resourceType:AddTagsToResource' :: AddTagsToResource -> ResourceTypeForTagging
..} =
forall a. NFData a => a -> ()
Prelude.rnf ResourceTypeForTagging
resourceType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Tag]
tags
instance Data.ToHeaders AddTagsToResource where
toHeaders :: AddTagsToResource -> 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
"AmazonSSM.AddTagsToResource" ::
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 AddTagsToResource where
toJSON :: AddTagsToResource -> Value
toJSON AddTagsToResource' {[Tag]
Text
ResourceTypeForTagging
tags :: [Tag]
resourceId :: Text
resourceType :: ResourceTypeForTagging
$sel:tags:AddTagsToResource' :: AddTagsToResource -> [Tag]
$sel:resourceId:AddTagsToResource' :: AddTagsToResource -> Text
$sel:resourceType:AddTagsToResource' :: AddTagsToResource -> ResourceTypeForTagging
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just (Key
"ResourceType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ResourceTypeForTagging
resourceType),
forall a. a -> Maybe a
Prelude.Just (Key
"ResourceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceId),
forall a. a -> Maybe a
Prelude.Just (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Tag]
tags)
]
)
instance Data.ToPath AddTagsToResource where
toPath :: AddTagsToResource -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery AddTagsToResource where
toQuery :: AddTagsToResource -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data AddTagsToResourceResponse = AddTagsToResourceResponse'
{
AddTagsToResourceResponse -> Int
httpStatus :: Prelude.Int
}
deriving (AddTagsToResourceResponse -> AddTagsToResourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddTagsToResourceResponse -> AddTagsToResourceResponse -> Bool
$c/= :: AddTagsToResourceResponse -> AddTagsToResourceResponse -> Bool
== :: AddTagsToResourceResponse -> AddTagsToResourceResponse -> Bool
$c== :: AddTagsToResourceResponse -> AddTagsToResourceResponse -> Bool
Prelude.Eq, ReadPrec [AddTagsToResourceResponse]
ReadPrec AddTagsToResourceResponse
Int -> ReadS AddTagsToResourceResponse
ReadS [AddTagsToResourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddTagsToResourceResponse]
$creadListPrec :: ReadPrec [AddTagsToResourceResponse]
readPrec :: ReadPrec AddTagsToResourceResponse
$creadPrec :: ReadPrec AddTagsToResourceResponse
readList :: ReadS [AddTagsToResourceResponse]
$creadList :: ReadS [AddTagsToResourceResponse]
readsPrec :: Int -> ReadS AddTagsToResourceResponse
$creadsPrec :: Int -> ReadS AddTagsToResourceResponse
Prelude.Read, Int -> AddTagsToResourceResponse -> ShowS
[AddTagsToResourceResponse] -> ShowS
AddTagsToResourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddTagsToResourceResponse] -> ShowS
$cshowList :: [AddTagsToResourceResponse] -> ShowS
show :: AddTagsToResourceResponse -> String
$cshow :: AddTagsToResourceResponse -> String
showsPrec :: Int -> AddTagsToResourceResponse -> ShowS
$cshowsPrec :: Int -> AddTagsToResourceResponse -> ShowS
Prelude.Show, forall x.
Rep AddTagsToResourceResponse x -> AddTagsToResourceResponse
forall x.
AddTagsToResourceResponse -> Rep AddTagsToResourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AddTagsToResourceResponse x -> AddTagsToResourceResponse
$cfrom :: forall x.
AddTagsToResourceResponse -> Rep AddTagsToResourceResponse x
Prelude.Generic)
newAddTagsToResourceResponse ::
Prelude.Int ->
AddTagsToResourceResponse
newAddTagsToResourceResponse :: Int -> AddTagsToResourceResponse
newAddTagsToResourceResponse Int
pHttpStatus_ =
AddTagsToResourceResponse'
{ $sel:httpStatus:AddTagsToResourceResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
addTagsToResourceResponse_httpStatus :: Lens.Lens' AddTagsToResourceResponse Prelude.Int
addTagsToResourceResponse_httpStatus :: Lens' AddTagsToResourceResponse Int
addTagsToResourceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddTagsToResourceResponse' {Int
httpStatus :: Int
$sel:httpStatus:AddTagsToResourceResponse' :: AddTagsToResourceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AddTagsToResourceResponse
s@AddTagsToResourceResponse' {} Int
a -> AddTagsToResourceResponse
s {$sel:httpStatus:AddTagsToResourceResponse' :: Int
httpStatus = Int
a} :: AddTagsToResourceResponse)
instance Prelude.NFData AddTagsToResourceResponse where
rnf :: AddTagsToResourceResponse -> ()
rnf AddTagsToResourceResponse' {Int
httpStatus :: Int
$sel:httpStatus:AddTagsToResourceResponse' :: AddTagsToResourceResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus