{-# 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.ListTagsForStream
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of tags associated with the specified stream.
--
-- In the request, you must specify either the @StreamName@ or the
-- @StreamARN@.
module Amazonka.KinesisVideo.ListTagsForStream
  ( -- * Creating a Request
    ListTagsForStream (..),
    newListTagsForStream,

    -- * Request Lenses
    listTagsForStream_nextToken,
    listTagsForStream_streamARN,
    listTagsForStream_streamName,

    -- * Destructuring the Response
    ListTagsForStreamResponse (..),
    newListTagsForStreamResponse,

    -- * Response Lenses
    listTagsForStreamResponse_nextToken,
    listTagsForStreamResponse_tags,
    listTagsForStreamResponse_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:/ 'newListTagsForStream' smart constructor.
data ListTagsForStream = ListTagsForStream'
  { -- | If you specify this parameter and the result of a @ListTagsForStream@
    -- call is truncated, the response includes a token that you can use in the
    -- next request to fetch the next batch of tags.
    ListTagsForStream -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the stream that you want to list tags
    -- for.
    ListTagsForStream -> Maybe Text
streamARN :: Prelude.Maybe Prelude.Text,
    -- | The name of the stream that you want to list tags for.
    ListTagsForStream -> Maybe Text
streamName :: Prelude.Maybe Prelude.Text
  }
  deriving (ListTagsForStream -> ListTagsForStream -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTagsForStream -> ListTagsForStream -> Bool
$c/= :: ListTagsForStream -> ListTagsForStream -> Bool
== :: ListTagsForStream -> ListTagsForStream -> Bool
$c== :: ListTagsForStream -> ListTagsForStream -> Bool
Prelude.Eq, ReadPrec [ListTagsForStream]
ReadPrec ListTagsForStream
Int -> ReadS ListTagsForStream
ReadS [ListTagsForStream]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTagsForStream]
$creadListPrec :: ReadPrec [ListTagsForStream]
readPrec :: ReadPrec ListTagsForStream
$creadPrec :: ReadPrec ListTagsForStream
readList :: ReadS [ListTagsForStream]
$creadList :: ReadS [ListTagsForStream]
readsPrec :: Int -> ReadS ListTagsForStream
$creadsPrec :: Int -> ReadS ListTagsForStream
Prelude.Read, Int -> ListTagsForStream -> ShowS
[ListTagsForStream] -> ShowS
ListTagsForStream -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTagsForStream] -> ShowS
$cshowList :: [ListTagsForStream] -> ShowS
show :: ListTagsForStream -> String
$cshow :: ListTagsForStream -> String
showsPrec :: Int -> ListTagsForStream -> ShowS
$cshowsPrec :: Int -> ListTagsForStream -> ShowS
Prelude.Show, forall x. Rep ListTagsForStream x -> ListTagsForStream
forall x. ListTagsForStream -> Rep ListTagsForStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTagsForStream x -> ListTagsForStream
$cfrom :: forall x. ListTagsForStream -> Rep ListTagsForStream x
Prelude.Generic)

-- |
-- Create a value of 'ListTagsForStream' 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:
--
-- 'nextToken', 'listTagsForStream_nextToken' - If you specify this parameter and the result of a @ListTagsForStream@
-- call is truncated, the response includes a token that you can use in the
-- next request to fetch the next batch of tags.
--
-- 'streamARN', 'listTagsForStream_streamARN' - The Amazon Resource Name (ARN) of the stream that you want to list tags
-- for.
--
-- 'streamName', 'listTagsForStream_streamName' - The name of the stream that you want to list tags for.
newListTagsForStream ::
  ListTagsForStream
newListTagsForStream :: ListTagsForStream
newListTagsForStream =
  ListTagsForStream'
    { $sel:nextToken:ListTagsForStream' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:streamARN:ListTagsForStream' :: Maybe Text
streamARN = forall a. Maybe a
Prelude.Nothing,
      $sel:streamName:ListTagsForStream' :: Maybe Text
streamName = forall a. Maybe a
Prelude.Nothing
    }

-- | If you specify this parameter and the result of a @ListTagsForStream@
-- call is truncated, the response includes a token that you can use in the
-- next request to fetch the next batch of tags.
listTagsForStream_nextToken :: Lens.Lens' ListTagsForStream (Prelude.Maybe Prelude.Text)
listTagsForStream_nextToken :: Lens' ListTagsForStream (Maybe Text)
listTagsForStream_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForStream' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTagsForStream' :: ListTagsForStream -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTagsForStream
s@ListTagsForStream' {} Maybe Text
a -> ListTagsForStream
s {$sel:nextToken:ListTagsForStream' :: Maybe Text
nextToken = Maybe Text
a} :: ListTagsForStream)

-- | The Amazon Resource Name (ARN) of the stream that you want to list tags
-- for.
listTagsForStream_streamARN :: Lens.Lens' ListTagsForStream (Prelude.Maybe Prelude.Text)
listTagsForStream_streamARN :: Lens' ListTagsForStream (Maybe Text)
listTagsForStream_streamARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForStream' {Maybe Text
streamARN :: Maybe Text
$sel:streamARN:ListTagsForStream' :: ListTagsForStream -> Maybe Text
streamARN} -> Maybe Text
streamARN) (\s :: ListTagsForStream
s@ListTagsForStream' {} Maybe Text
a -> ListTagsForStream
s {$sel:streamARN:ListTagsForStream' :: Maybe Text
streamARN = Maybe Text
a} :: ListTagsForStream)

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

instance Core.AWSRequest ListTagsForStream where
  type
    AWSResponse ListTagsForStream =
      ListTagsForStreamResponse
  request :: (Service -> Service)
-> ListTagsForStream -> Request ListTagsForStream
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 ListTagsForStream
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListTagsForStream)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe (HashMap Text Text) -> Int -> ListTagsForStreamResponse
ListTagsForStreamResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => 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 ListTagsForStream where
  hashWithSalt :: Int -> ListTagsForStream -> Int
hashWithSalt Int
_salt ListTagsForStream' {Maybe Text
streamName :: Maybe Text
streamARN :: Maybe Text
nextToken :: Maybe Text
$sel:streamName:ListTagsForStream' :: ListTagsForStream -> Maybe Text
$sel:streamARN:ListTagsForStream' :: ListTagsForStream -> Maybe Text
$sel:nextToken:ListTagsForStream' :: ListTagsForStream -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamName

instance Prelude.NFData ListTagsForStream where
  rnf :: ListTagsForStream -> ()
rnf ListTagsForStream' {Maybe Text
streamName :: Maybe Text
streamARN :: Maybe Text
nextToken :: Maybe Text
$sel:streamName:ListTagsForStream' :: ListTagsForStream -> Maybe Text
$sel:streamARN:ListTagsForStream' :: ListTagsForStream -> Maybe Text
$sel:nextToken:ListTagsForStream' :: ListTagsForStream -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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

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

instance Data.ToJSON ListTagsForStream where
  toJSON :: ListTagsForStream -> Value
toJSON ListTagsForStream' {Maybe Text
streamName :: Maybe Text
streamARN :: Maybe Text
nextToken :: Maybe Text
$sel:streamName:ListTagsForStream' :: ListTagsForStream -> Maybe Text
$sel:streamARN:ListTagsForStream' :: ListTagsForStream -> Maybe Text
$sel:nextToken:ListTagsForStream' :: ListTagsForStream -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"NextToken" 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
nextToken,
            (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
          ]
      )

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

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

-- | /See:/ 'newListTagsForStreamResponse' smart constructor.
data ListTagsForStreamResponse = ListTagsForStreamResponse'
  { -- | If you specify this parameter and the result of a @ListTags@ call is
    -- truncated, the response includes a token that you can use in the next
    -- request to fetch the next set of tags.
    ListTagsForStreamResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A map of tag keys and values associated with the specified stream.
    ListTagsForStreamResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    ListTagsForStreamResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListTagsForStreamResponse -> ListTagsForStreamResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTagsForStreamResponse -> ListTagsForStreamResponse -> Bool
$c/= :: ListTagsForStreamResponse -> ListTagsForStreamResponse -> Bool
== :: ListTagsForStreamResponse -> ListTagsForStreamResponse -> Bool
$c== :: ListTagsForStreamResponse -> ListTagsForStreamResponse -> Bool
Prelude.Eq, ReadPrec [ListTagsForStreamResponse]
ReadPrec ListTagsForStreamResponse
Int -> ReadS ListTagsForStreamResponse
ReadS [ListTagsForStreamResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTagsForStreamResponse]
$creadListPrec :: ReadPrec [ListTagsForStreamResponse]
readPrec :: ReadPrec ListTagsForStreamResponse
$creadPrec :: ReadPrec ListTagsForStreamResponse
readList :: ReadS [ListTagsForStreamResponse]
$creadList :: ReadS [ListTagsForStreamResponse]
readsPrec :: Int -> ReadS ListTagsForStreamResponse
$creadsPrec :: Int -> ReadS ListTagsForStreamResponse
Prelude.Read, Int -> ListTagsForStreamResponse -> ShowS
[ListTagsForStreamResponse] -> ShowS
ListTagsForStreamResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTagsForStreamResponse] -> ShowS
$cshowList :: [ListTagsForStreamResponse] -> ShowS
show :: ListTagsForStreamResponse -> String
$cshow :: ListTagsForStreamResponse -> String
showsPrec :: Int -> ListTagsForStreamResponse -> ShowS
$cshowsPrec :: Int -> ListTagsForStreamResponse -> ShowS
Prelude.Show, forall x.
Rep ListTagsForStreamResponse x -> ListTagsForStreamResponse
forall x.
ListTagsForStreamResponse -> Rep ListTagsForStreamResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListTagsForStreamResponse x -> ListTagsForStreamResponse
$cfrom :: forall x.
ListTagsForStreamResponse -> Rep ListTagsForStreamResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTagsForStreamResponse' 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:
--
-- 'nextToken', 'listTagsForStreamResponse_nextToken' - If you specify this parameter and the result of a @ListTags@ call is
-- truncated, the response includes a token that you can use in the next
-- request to fetch the next set of tags.
--
-- 'tags', 'listTagsForStreamResponse_tags' - A map of tag keys and values associated with the specified stream.
--
-- 'httpStatus', 'listTagsForStreamResponse_httpStatus' - The response's http status code.
newListTagsForStreamResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTagsForStreamResponse
newListTagsForStreamResponse :: Int -> ListTagsForStreamResponse
newListTagsForStreamResponse Int
pHttpStatus_ =
  ListTagsForStreamResponse'
    { $sel:nextToken:ListTagsForStreamResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ListTagsForStreamResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTagsForStreamResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If you specify this parameter and the result of a @ListTags@ call is
-- truncated, the response includes a token that you can use in the next
-- request to fetch the next set of tags.
listTagsForStreamResponse_nextToken :: Lens.Lens' ListTagsForStreamResponse (Prelude.Maybe Prelude.Text)
listTagsForStreamResponse_nextToken :: Lens' ListTagsForStreamResponse (Maybe Text)
listTagsForStreamResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForStreamResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTagsForStreamResponse' :: ListTagsForStreamResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTagsForStreamResponse
s@ListTagsForStreamResponse' {} Maybe Text
a -> ListTagsForStreamResponse
s {$sel:nextToken:ListTagsForStreamResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListTagsForStreamResponse)

-- | A map of tag keys and values associated with the specified stream.
listTagsForStreamResponse_tags :: Lens.Lens' ListTagsForStreamResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
listTagsForStreamResponse_tags :: Lens' ListTagsForStreamResponse (Maybe (HashMap Text Text))
listTagsForStreamResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForStreamResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:ListTagsForStreamResponse' :: ListTagsForStreamResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: ListTagsForStreamResponse
s@ListTagsForStreamResponse' {} Maybe (HashMap Text Text)
a -> ListTagsForStreamResponse
s {$sel:tags:ListTagsForStreamResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: ListTagsForStreamResponse) 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

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

instance Prelude.NFData ListTagsForStreamResponse where
  rnf :: ListTagsForStreamResponse -> ()
rnf ListTagsForStreamResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
nextToken :: Maybe Text
$sel:httpStatus:ListTagsForStreamResponse' :: ListTagsForStreamResponse -> Int
$sel:tags:ListTagsForStreamResponse' :: ListTagsForStreamResponse -> Maybe (HashMap Text Text)
$sel:nextToken:ListTagsForStreamResponse' :: ListTagsForStreamResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Int
httpStatus