{-# 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.MediaStore.TagResource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds tags to the specified AWS Elemental MediaStore container. Tags are
-- key:value pairs that you can associate with AWS resources. For example,
-- the tag key might be \"customer\" and the tag value might be
-- \"companyA.\" You can specify one or more tags to add to each container.
-- You can add up to 50 tags to each container. For more information about
-- tagging, including naming and usage conventions, see
-- <https://docs.aws.amazon.com/mediastore/latest/ug/tagging.html Tagging Resources in MediaStore>.
module Amazonka.MediaStore.TagResource
  ( -- * Creating a Request
    TagResource (..),
    newTagResource,

    -- * Request Lenses
    tagResource_resource,
    tagResource_tags,

    -- * Destructuring the Response
    TagResourceResponse (..),
    newTagResourceResponse,

    -- * Response Lenses
    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.MediaStore.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newTagResource' smart constructor.
data TagResource = TagResource'
  { -- | The Amazon Resource Name (ARN) for the container.
    TagResource -> Text
resource :: Prelude.Text,
    -- | An array of key:value pairs that you want to add to the container. You
    -- need to specify only the tags that you want to add or update. For
    -- example, suppose a container already has two tags (customer:CompanyA and
    -- priority:High). You want to change the priority tag and also add a third
    -- tag (type:Contract). For TagResource, you specify the following tags:
    -- priority:Medium, type:Contract. The result is that your container has
    -- three tags: customer:CompanyA, priority:Medium, and type:Contract.
    TagResource -> NonEmpty Tag
tags :: Prelude.NonEmpty Tag
  }
  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)

-- |
-- Create a value of 'TagResource' 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:
--
-- 'resource', 'tagResource_resource' - The Amazon Resource Name (ARN) for the container.
--
-- 'tags', 'tagResource_tags' - An array of key:value pairs that you want to add to the container. You
-- need to specify only the tags that you want to add or update. For
-- example, suppose a container already has two tags (customer:CompanyA and
-- priority:High). You want to change the priority tag and also add a third
-- tag (type:Contract). For TagResource, you specify the following tags:
-- priority:Medium, type:Contract. The result is that your container has
-- three tags: customer:CompanyA, priority:Medium, and type:Contract.
newTagResource ::
  -- | 'resource'
  Prelude.Text ->
  -- | 'tags'
  Prelude.NonEmpty Tag ->
  TagResource
newTagResource :: Text -> NonEmpty Tag -> TagResource
newTagResource Text
pResource_ NonEmpty Tag
pTags_ =
  TagResource'
    { $sel:resource:TagResource' :: Text
resource = Text
pResource_,
      $sel:tags:TagResource' :: NonEmpty Tag
tags = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Tag
pTags_
    }

-- | The Amazon Resource Name (ARN) for the container.
tagResource_resource :: Lens.Lens' TagResource Prelude.Text
tagResource_resource :: Lens' TagResource Text
tagResource_resource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResource' {Text
resource :: Text
$sel:resource:TagResource' :: TagResource -> Text
resource} -> Text
resource) (\s :: TagResource
s@TagResource' {} Text
a -> TagResource
s {$sel:resource:TagResource' :: Text
resource = Text
a} :: TagResource)

-- | An array of key:value pairs that you want to add to the container. You
-- need to specify only the tags that you want to add or update. For
-- example, suppose a container already has two tags (customer:CompanyA and
-- priority:High). You want to change the priority tag and also add a third
-- tag (type:Contract). For TagResource, you specify the following tags:
-- priority:Medium, type:Contract. The result is that your container has
-- three tags: customer:CompanyA, priority:Medium, and type:Contract.
tagResource_tags :: Lens.Lens' TagResource (Prelude.NonEmpty Tag)
tagResource_tags :: Lens' TagResource (NonEmpty Tag)
tagResource_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResource' {NonEmpty Tag
tags :: NonEmpty Tag
$sel:tags:TagResource' :: TagResource -> NonEmpty Tag
tags} -> NonEmpty Tag
tags) (\s :: TagResource
s@TagResource' {} NonEmpty Tag
a -> TagResource
s {$sel:tags:TagResource' :: NonEmpty Tag
tags = NonEmpty Tag
a} :: TagResource) 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 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' {NonEmpty Tag
Text
tags :: NonEmpty Tag
resource :: Text
$sel:tags:TagResource' :: TagResource -> NonEmpty Tag
$sel:resource:TagResource' :: TagResource -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Tag
tags

instance Prelude.NFData TagResource where
  rnf :: TagResource -> ()
rnf TagResource' {NonEmpty Tag
Text
tags :: NonEmpty Tag
resource :: Text
$sel:tags:TagResource' :: TagResource -> NonEmpty Tag
$sel:resource:TagResource' :: TagResource -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
resource seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Tag
tags

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
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"MediaStore_20170901.TagResource" ::
                          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 TagResource where
  toJSON :: TagResource -> Value
toJSON TagResource' {NonEmpty Tag
Text
tags :: NonEmpty Tag
resource :: Text
$sel:tags:TagResource' :: TagResource -> NonEmpty Tag
$sel:resource:TagResource' :: TagResource -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"Resource" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resource),
            forall a. a -> Maybe a
Prelude.Just (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Tag
tags)
          ]
      )

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

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

-- | /See:/ 'newTagResourceResponse' smart constructor.
data TagResourceResponse = TagResourceResponse'
  { -- | The response's http status code.
    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)

-- |
-- Create a value of 'TagResourceResponse' 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:
--
-- 'httpStatus', 'tagResourceResponse_httpStatus' - The response's http status code.
newTagResourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  TagResourceResponse
newTagResourceResponse :: Int -> TagResourceResponse
newTagResourceResponse Int
pHttpStatus_ =
  TagResourceResponse' {$sel:httpStatus:TagResourceResponse' :: Int
httpStatus = Int
pHttpStatus_}

-- | The response's http status code.
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