{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Network.AWS.DynamoDB.TagResource
(
tagResource
, TagResource
, trResourceARN
, trTags
, tagResourceResponse
, TagResourceResponse
) where
import Network.AWS.DynamoDB.Types
import Network.AWS.DynamoDB.Types.Product
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data TagResource = TagResource'
{ _trResourceARN :: !Text
, _trTags :: ![Tag]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
tagResource
:: Text
-> TagResource
tagResource pResourceARN_ =
TagResource' {_trResourceARN = pResourceARN_, _trTags = mempty}
trResourceARN :: Lens' TagResource Text
trResourceARN = lens _trResourceARN (\ s a -> s{_trResourceARN = a})
trTags :: Lens' TagResource [Tag]
trTags = lens _trTags (\ s a -> s{_trTags = a}) . _Coerce
instance AWSRequest TagResource where
type Rs TagResource = TagResourceResponse
request = postJSON dynamoDB
response = receiveNull TagResourceResponse'
instance Hashable TagResource where
instance NFData TagResource where
instance ToHeaders TagResource where
toHeaders
= const
(mconcat
["X-Amz-Target" =#
("DynamoDB_20120810.TagResource" :: ByteString),
"Content-Type" =#
("application/x-amz-json-1.0" :: ByteString)])
instance ToJSON TagResource where
toJSON TagResource'{..}
= object
(catMaybes
[Just ("ResourceArn" .= _trResourceARN),
Just ("Tags" .= _trTags)])
instance ToPath TagResource where
toPath = const "/"
instance ToQuery TagResource where
toQuery = const mempty
data TagResourceResponse =
TagResourceResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
tagResourceResponse
:: TagResourceResponse
tagResourceResponse = TagResourceResponse'
instance NFData TagResourceResponse where