{-# 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.KinesisVideo.TagStream
-- 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 one or more tags to a stream. A /tag/ is a key-value pair (the
-- value is optional) that you can define and assign to Amazon Web Services
-- resources. If you specify a tag that already exists, the tag value is
-- replaced with the value that you specify in the request. For more
-- information, see
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html Using Cost Allocation Tags>
-- in the /Billing and Cost Management and Cost Management User Guide/.
--
-- You must provide either the @StreamName@ or the @StreamARN@.
--
-- This operation requires permission for the @KinesisVideo:TagStream@
-- action.
--
-- A Kinesis video stream can support up to 50 tags.
module Amazonka.KinesisVideo.TagStream
  ( -- * Creating a Request
    TagStream (..),
    newTagStream,

    -- * Request Lenses
    tagStream_streamARN,
    tagStream_streamName,
    tagStream_tags,

    -- * Destructuring the Response
    TagStreamResponse (..),
    newTagStreamResponse,

    -- * Response Lenses
    tagStreamResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KinesisVideo.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newTagStream' smart constructor.
data TagStream = TagStream'
  { -- | The Amazon Resource Name (ARN) of the resource that you want to add the
    -- tag or tags to.
    TagStream -> Maybe Text
streamARN :: Prelude.Maybe Prelude.Text,
    -- | The name of the stream that you want to add the tag or tags to.
    TagStream -> Maybe Text
streamName :: Prelude.Maybe Prelude.Text,
    -- | A list of tags to associate with the specified stream. Each tag is a
    -- key-value pair (the value is optional).
    TagStream -> HashMap Text Text
tags :: Prelude.HashMap Prelude.Text Prelude.Text
  }
  deriving (TagStream -> TagStream -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagStream -> TagStream -> Bool
$c/= :: TagStream -> TagStream -> Bool
== :: TagStream -> TagStream -> Bool
$c== :: TagStream -> TagStream -> Bool
Prelude.Eq, ReadPrec [TagStream]
ReadPrec TagStream
Int -> ReadS TagStream
ReadS [TagStream]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagStream]
$creadListPrec :: ReadPrec [TagStream]
readPrec :: ReadPrec TagStream
$creadPrec :: ReadPrec TagStream
readList :: ReadS [TagStream]
$creadList :: ReadS [TagStream]
readsPrec :: Int -> ReadS TagStream
$creadsPrec :: Int -> ReadS TagStream
Prelude.Read, Int -> TagStream -> ShowS
[TagStream] -> ShowS
TagStream -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagStream] -> ShowS
$cshowList :: [TagStream] -> ShowS
show :: TagStream -> String
$cshow :: TagStream -> String
showsPrec :: Int -> TagStream -> ShowS
$cshowsPrec :: Int -> TagStream -> ShowS
Prelude.Show, forall x. Rep TagStream x -> TagStream
forall x. TagStream -> Rep TagStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagStream x -> TagStream
$cfrom :: forall x. TagStream -> Rep TagStream x
Prelude.Generic)

-- |
-- Create a value of 'TagStream' 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:
--
-- 'streamARN', 'tagStream_streamARN' - The Amazon Resource Name (ARN) of the resource that you want to add the
-- tag or tags to.
--
-- 'streamName', 'tagStream_streamName' - The name of the stream that you want to add the tag or tags to.
--
-- 'tags', 'tagStream_tags' - A list of tags to associate with the specified stream. Each tag is a
-- key-value pair (the value is optional).
newTagStream ::
  TagStream
newTagStream :: TagStream
newTagStream =
  TagStream'
    { $sel:streamARN:TagStream' :: Maybe Text
streamARN = forall a. Maybe a
Prelude.Nothing,
      $sel:streamName:TagStream' :: Maybe Text
streamName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:TagStream' :: HashMap Text Text
tags = forall a. Monoid a => a
Prelude.mempty
    }

-- | The Amazon Resource Name (ARN) of the resource that you want to add the
-- tag or tags to.
tagStream_streamARN :: Lens.Lens' TagStream (Prelude.Maybe Prelude.Text)
tagStream_streamARN :: Lens' TagStream (Maybe Text)
tagStream_streamARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagStream' {Maybe Text
streamARN :: Maybe Text
$sel:streamARN:TagStream' :: TagStream -> Maybe Text
streamARN} -> Maybe Text
streamARN) (\s :: TagStream
s@TagStream' {} Maybe Text
a -> TagStream
s {$sel:streamARN:TagStream' :: Maybe Text
streamARN = Maybe Text
a} :: TagStream)

-- | The name of the stream that you want to add the tag or tags to.
tagStream_streamName :: Lens.Lens' TagStream (Prelude.Maybe Prelude.Text)
tagStream_streamName :: Lens' TagStream (Maybe Text)
tagStream_streamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagStream' {Maybe Text
streamName :: Maybe Text
$sel:streamName:TagStream' :: TagStream -> Maybe Text
streamName} -> Maybe Text
streamName) (\s :: TagStream
s@TagStream' {} Maybe Text
a -> TagStream
s {$sel:streamName:TagStream' :: Maybe Text
streamName = Maybe Text
a} :: TagStream)

-- | A list of tags to associate with the specified stream. Each tag is a
-- key-value pair (the value is optional).
tagStream_tags :: Lens.Lens' TagStream (Prelude.HashMap Prelude.Text Prelude.Text)
tagStream_tags :: Lens' TagStream (HashMap Text Text)
tagStream_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagStream' {HashMap Text Text
tags :: HashMap Text Text
$sel:tags:TagStream' :: TagStream -> HashMap Text Text
tags} -> HashMap Text Text
tags) (\s :: TagStream
s@TagStream' {} HashMap Text Text
a -> TagStream
s {$sel:tags:TagStream' :: HashMap Text Text
tags = HashMap Text Text
a} :: TagStream) 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 TagStream where
  type AWSResponse TagStream = TagStreamResponse
  request :: (Service -> Service) -> TagStream -> Request TagStream
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 TagStream
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse TagStream)))
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 -> TagStreamResponse
TagStreamResponse'
            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 TagStream where
  hashWithSalt :: Int -> TagStream -> Int
hashWithSalt Int
_salt TagStream' {Maybe Text
HashMap Text Text
tags :: HashMap Text Text
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:tags:TagStream' :: TagStream -> HashMap Text Text
$sel:streamName:TagStream' :: TagStream -> Maybe Text
$sel:streamARN:TagStream' :: TagStream -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HashMap Text Text
tags

instance Prelude.NFData TagStream where
  rnf :: TagStream -> ()
rnf TagStream' {Maybe Text
HashMap Text Text
tags :: HashMap Text Text
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:tags:TagStream' :: TagStream -> HashMap Text Text
$sel:streamName:TagStream' :: TagStream -> Maybe Text
$sel:streamARN:TagStream' :: TagStream -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HashMap Text Text
tags

instance Data.ToHeaders TagStream where
  toHeaders :: TagStream -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON TagStream where
  toJSON :: TagStream -> Value
toJSON TagStream' {Maybe Text
HashMap Text Text
tags :: HashMap Text Text
streamName :: Maybe Text
streamARN :: Maybe Text
$sel:tags:TagStream' :: TagStream -> HashMap Text Text
$sel:streamName:TagStream' :: TagStream -> Maybe Text
$sel:streamARN:TagStream' :: TagStream -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"StreamARN" 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 Text
streamARN,
            (Key
"StreamName" 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 Text
streamName,
            forall a. a -> Maybe a
Prelude.Just (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= HashMap Text Text
tags)
          ]
      )

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

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

-- | /See:/ 'newTagStreamResponse' smart constructor.
data TagStreamResponse = TagStreamResponse'
  { -- | The response's http status code.
    TagStreamResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (TagStreamResponse -> TagStreamResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagStreamResponse -> TagStreamResponse -> Bool
$c/= :: TagStreamResponse -> TagStreamResponse -> Bool
== :: TagStreamResponse -> TagStreamResponse -> Bool
$c== :: TagStreamResponse -> TagStreamResponse -> Bool
Prelude.Eq, ReadPrec [TagStreamResponse]
ReadPrec TagStreamResponse
Int -> ReadS TagStreamResponse
ReadS [TagStreamResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagStreamResponse]
$creadListPrec :: ReadPrec [TagStreamResponse]
readPrec :: ReadPrec TagStreamResponse
$creadPrec :: ReadPrec TagStreamResponse
readList :: ReadS [TagStreamResponse]
$creadList :: ReadS [TagStreamResponse]
readsPrec :: Int -> ReadS TagStreamResponse
$creadsPrec :: Int -> ReadS TagStreamResponse
Prelude.Read, Int -> TagStreamResponse -> ShowS
[TagStreamResponse] -> ShowS
TagStreamResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagStreamResponse] -> ShowS
$cshowList :: [TagStreamResponse] -> ShowS
show :: TagStreamResponse -> String
$cshow :: TagStreamResponse -> String
showsPrec :: Int -> TagStreamResponse -> ShowS
$cshowsPrec :: Int -> TagStreamResponse -> ShowS
Prelude.Show, forall x. Rep TagStreamResponse x -> TagStreamResponse
forall x. TagStreamResponse -> Rep TagStreamResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagStreamResponse x -> TagStreamResponse
$cfrom :: forall x. TagStreamResponse -> Rep TagStreamResponse x
Prelude.Generic)

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

-- | The response's http status code.
tagStreamResponse_httpStatus :: Lens.Lens' TagStreamResponse Prelude.Int
tagStreamResponse_httpStatus :: Lens' TagStreamResponse Int
tagStreamResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagStreamResponse' {Int
httpStatus :: Int
$sel:httpStatus:TagStreamResponse' :: TagStreamResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: TagStreamResponse
s@TagStreamResponse' {} Int
a -> TagStreamResponse
s {$sel:httpStatus:TagStreamResponse' :: Int
httpStatus = Int
a} :: TagStreamResponse)

instance Prelude.NFData TagStreamResponse where
  rnf :: TagStreamResponse -> ()
rnf TagStreamResponse' {Int
httpStatus :: Int
$sel:httpStatus:TagStreamResponse' :: TagStreamResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus