{-# 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.Nimble.TagResource
(
TagResource (..),
newTagResource,
tagResource_tags,
tagResource_resourceArn,
TagResourceResponse (..),
newTagResourceResponse,
tagResourceResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Nimble.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data TagResource = TagResource'
{
TagResource -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
TagResource -> Text
resourceArn :: Prelude.Text
}
deriving (TagResource -> TagResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagResource -> TagResource -> Bool
$c/= :: TagResource -> TagResource -> Bool
== :: TagResource -> TagResource -> Bool
$c== :: TagResource -> TagResource -> Bool
Prelude.Eq, ReadPrec [TagResource]
ReadPrec TagResource
Int -> ReadS TagResource
ReadS [TagResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagResource]
$creadListPrec :: ReadPrec [TagResource]
readPrec :: ReadPrec TagResource
$creadPrec :: ReadPrec TagResource
readList :: ReadS [TagResource]
$creadList :: ReadS [TagResource]
readsPrec :: Int -> ReadS TagResource
$creadsPrec :: Int -> ReadS TagResource
Prelude.Read, Int -> TagResource -> ShowS
[TagResource] -> ShowS
TagResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagResource] -> ShowS
$cshowList :: [TagResource] -> ShowS
show :: TagResource -> String
$cshow :: TagResource -> String
showsPrec :: Int -> TagResource -> ShowS
$cshowsPrec :: Int -> TagResource -> ShowS
Prelude.Show, forall x. Rep TagResource x -> TagResource
forall x. TagResource -> Rep TagResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagResource x -> TagResource
$cfrom :: forall x. TagResource -> Rep TagResource x
Prelude.Generic)
newTagResource ::
Prelude.Text ->
TagResource
newTagResource :: Text -> TagResource
newTagResource Text
pResourceArn_ =
TagResource'
{ $sel:tags:TagResource' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
$sel:resourceArn:TagResource' :: Text
resourceArn = Text
pResourceArn_
}
tagResource_tags :: Lens.Lens' TagResource (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
tagResource_tags :: Lens' TagResource (Maybe (HashMap Text Text))
tagResource_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResource' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:TagResource' :: TagResource -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: TagResource
s@TagResource' {} Maybe (HashMap Text Text)
a -> TagResource
s {$sel:tags:TagResource' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: TagResource) 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
tagResource_resourceArn :: Lens.Lens' TagResource Prelude.Text
tagResource_resourceArn :: Lens' TagResource Text
tagResource_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResource' {Text
resourceArn :: Text
$sel:resourceArn:TagResource' :: TagResource -> Text
resourceArn} -> Text
resourceArn) (\s :: TagResource
s@TagResource' {} Text
a -> TagResource
s {$sel:resourceArn:TagResource' :: Text
resourceArn = Text
a} :: TagResource)
instance Core.AWSRequest TagResource where
type AWSResponse TagResource = TagResourceResponse
request :: (Service -> Service) -> TagResource -> Request TagResource
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 TagResource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse TagResource)))
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 -> TagResourceResponse
TagResourceResponse'
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 TagResource where
hashWithSalt :: Int -> TagResource -> Int
hashWithSalt Int
_salt TagResource' {Maybe (HashMap Text Text)
Text
resourceArn :: Text
tags :: Maybe (HashMap Text Text)
$sel:resourceArn:TagResource' :: TagResource -> Text
$sel:tags:TagResource' :: TagResource -> Maybe (HashMap Text Text)
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn
instance Prelude.NFData TagResource where
rnf :: TagResource -> ()
rnf TagResource' {Maybe (HashMap Text Text)
Text
resourceArn :: Text
tags :: Maybe (HashMap Text Text)
$sel:resourceArn:TagResource' :: TagResource -> Text
$sel:tags:TagResource' :: TagResource -> Maybe (HashMap Text Text)
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn
instance Data.ToHeaders TagResource where
toHeaders :: TagResource -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON TagResource where
toJSON :: TagResource -> Value
toJSON TagResource' {Maybe (HashMap Text Text)
Text
resourceArn :: Text
tags :: Maybe (HashMap Text Text)
$sel:resourceArn:TagResource' :: TagResource -> Text
$sel:tags:TagResource' :: TagResource -> Maybe (HashMap Text Text)
..} =
[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 (HashMap Text Text)
tags]
)
instance Data.ToPath TagResource where
toPath :: TagResource -> ByteString
toPath TagResource' {Maybe (HashMap Text Text)
Text
resourceArn :: Text
tags :: Maybe (HashMap Text Text)
$sel:resourceArn:TagResource' :: TagResource -> Text
$sel:tags:TagResource' :: TagResource -> Maybe (HashMap Text Text)
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/2020-08-01/tags/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
resourceArn]
instance Data.ToQuery TagResource where
toQuery :: TagResource -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data TagResourceResponse = TagResourceResponse'
{
TagResourceResponse -> Int
httpStatus :: Prelude.Int
}
deriving (TagResourceResponse -> TagResourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagResourceResponse -> TagResourceResponse -> Bool
$c/= :: TagResourceResponse -> TagResourceResponse -> Bool
== :: TagResourceResponse -> TagResourceResponse -> Bool
$c== :: TagResourceResponse -> TagResourceResponse -> Bool
Prelude.Eq, ReadPrec [TagResourceResponse]
ReadPrec TagResourceResponse
Int -> ReadS TagResourceResponse
ReadS [TagResourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagResourceResponse]
$creadListPrec :: ReadPrec [TagResourceResponse]
readPrec :: ReadPrec TagResourceResponse
$creadPrec :: ReadPrec TagResourceResponse
readList :: ReadS [TagResourceResponse]
$creadList :: ReadS [TagResourceResponse]
readsPrec :: Int -> ReadS TagResourceResponse
$creadsPrec :: Int -> ReadS TagResourceResponse
Prelude.Read, Int -> TagResourceResponse -> ShowS
[TagResourceResponse] -> ShowS
TagResourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagResourceResponse] -> ShowS
$cshowList :: [TagResourceResponse] -> ShowS
show :: TagResourceResponse -> String
$cshow :: TagResourceResponse -> String
showsPrec :: Int -> TagResourceResponse -> ShowS
$cshowsPrec :: Int -> TagResourceResponse -> ShowS
Prelude.Show, forall x. Rep TagResourceResponse x -> TagResourceResponse
forall x. TagResourceResponse -> Rep TagResourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagResourceResponse x -> TagResourceResponse
$cfrom :: forall x. TagResourceResponse -> Rep TagResourceResponse x
Prelude.Generic)
newTagResourceResponse ::
Prelude.Int ->
TagResourceResponse
newTagResourceResponse :: Int -> TagResourceResponse
newTagResourceResponse Int
pHttpStatus_ =
TagResourceResponse' {$sel:httpStatus:TagResourceResponse' :: Int
httpStatus = Int
pHttpStatus_}
tagResourceResponse_httpStatus :: Lens.Lens' TagResourceResponse Prelude.Int
tagResourceResponse_httpStatus :: Lens' TagResourceResponse Int
tagResourceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResourceResponse' {Int
httpStatus :: Int
$sel:httpStatus:TagResourceResponse' :: TagResourceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: TagResourceResponse
s@TagResourceResponse' {} Int
a -> TagResourceResponse
s {$sel:httpStatus:TagResourceResponse' :: Int
httpStatus = Int
a} :: TagResourceResponse)
instance Prelude.NFData TagResourceResponse where
rnf :: TagResourceResponse -> ()
rnf TagResourceResponse' {Int
httpStatus :: Int
$sel:httpStatus:TagResourceResponse' :: TagResourceResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus