{-# 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.LicenseManager.ListTokens
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists your tokens.
module Amazonka.LicenseManager.ListTokens
  ( -- * Creating a Request
    ListTokens (..),
    newListTokens,

    -- * Request Lenses
    listTokens_filters,
    listTokens_maxResults,
    listTokens_nextToken,
    listTokens_tokenIds,

    -- * Destructuring the Response
    ListTokensResponse (..),
    newListTokensResponse,

    -- * Response Lenses
    listTokensResponse_nextToken,
    listTokensResponse_tokens,
    listTokensResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListTokens' smart constructor.
data ListTokens = ListTokens'
  { -- | Filters to scope the results. The following filter is supported:
    --
    -- -   @LicenseArns@
    ListTokens -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | Maximum number of results to return in a single call.
    ListTokens -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Token for the next set of results.
    ListTokens -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Token IDs.
    ListTokens -> Maybe [Text]
tokenIds :: Prelude.Maybe [Prelude.Text]
  }
  deriving (ListTokens -> ListTokens -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTokens -> ListTokens -> Bool
$c/= :: ListTokens -> ListTokens -> Bool
== :: ListTokens -> ListTokens -> Bool
$c== :: ListTokens -> ListTokens -> Bool
Prelude.Eq, ReadPrec [ListTokens]
ReadPrec ListTokens
Int -> ReadS ListTokens
ReadS [ListTokens]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTokens]
$creadListPrec :: ReadPrec [ListTokens]
readPrec :: ReadPrec ListTokens
$creadPrec :: ReadPrec ListTokens
readList :: ReadS [ListTokens]
$creadList :: ReadS [ListTokens]
readsPrec :: Int -> ReadS ListTokens
$creadsPrec :: Int -> ReadS ListTokens
Prelude.Read, Int -> ListTokens -> ShowS
[ListTokens] -> ShowS
ListTokens -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTokens] -> ShowS
$cshowList :: [ListTokens] -> ShowS
show :: ListTokens -> String
$cshow :: ListTokens -> String
showsPrec :: Int -> ListTokens -> ShowS
$cshowsPrec :: Int -> ListTokens -> ShowS
Prelude.Show, forall x. Rep ListTokens x -> ListTokens
forall x. ListTokens -> Rep ListTokens x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTokens x -> ListTokens
$cfrom :: forall x. ListTokens -> Rep ListTokens x
Prelude.Generic)

-- |
-- Create a value of 'ListTokens' 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:
--
-- 'filters', 'listTokens_filters' - Filters to scope the results. The following filter is supported:
--
-- -   @LicenseArns@
--
-- 'maxResults', 'listTokens_maxResults' - Maximum number of results to return in a single call.
--
-- 'nextToken', 'listTokens_nextToken' - Token for the next set of results.
--
-- 'tokenIds', 'listTokens_tokenIds' - Token IDs.
newListTokens ::
  ListTokens
newListTokens :: ListTokens
newListTokens =
  ListTokens'
    { $sel:filters:ListTokens' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListTokens' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListTokens' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:tokenIds:ListTokens' :: Maybe [Text]
tokenIds = forall a. Maybe a
Prelude.Nothing
    }

-- | Filters to scope the results. The following filter is supported:
--
-- -   @LicenseArns@
listTokens_filters :: Lens.Lens' ListTokens (Prelude.Maybe [Filter])
listTokens_filters :: Lens' ListTokens (Maybe [Filter])
listTokens_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTokens' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:ListTokens' :: ListTokens -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: ListTokens
s@ListTokens' {} Maybe [Filter]
a -> ListTokens
s {$sel:filters:ListTokens' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: ListTokens) 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

-- | Maximum number of results to return in a single call.
listTokens_maxResults :: Lens.Lens' ListTokens (Prelude.Maybe Prelude.Natural)
listTokens_maxResults :: Lens' ListTokens (Maybe Natural)
listTokens_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTokens' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListTokens' :: ListTokens -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListTokens
s@ListTokens' {} Maybe Natural
a -> ListTokens
s {$sel:maxResults:ListTokens' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListTokens)

-- | Token for the next set of results.
listTokens_nextToken :: Lens.Lens' ListTokens (Prelude.Maybe Prelude.Text)
listTokens_nextToken :: Lens' ListTokens (Maybe Text)
listTokens_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTokens' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTokens' :: ListTokens -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTokens
s@ListTokens' {} Maybe Text
a -> ListTokens
s {$sel:nextToken:ListTokens' :: Maybe Text
nextToken = Maybe Text
a} :: ListTokens)

-- | Token IDs.
listTokens_tokenIds :: Lens.Lens' ListTokens (Prelude.Maybe [Prelude.Text])
listTokens_tokenIds :: Lens' ListTokens (Maybe [Text])
listTokens_tokenIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTokens' {Maybe [Text]
tokenIds :: Maybe [Text]
$sel:tokenIds:ListTokens' :: ListTokens -> Maybe [Text]
tokenIds} -> Maybe [Text]
tokenIds) (\s :: ListTokens
s@ListTokens' {} Maybe [Text]
a -> ListTokens
s {$sel:tokenIds:ListTokens' :: Maybe [Text]
tokenIds = Maybe [Text]
a} :: ListTokens) 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

instance Core.AWSRequest ListTokens where
  type AWSResponse ListTokens = ListTokensResponse
  request :: (Service -> Service) -> ListTokens -> Request ListTokens
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 ListTokens
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListTokens)))
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 [TokenData] -> Int -> ListTokensResponse
ListTokensResponse'
            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
"Tokens" 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 ListTokens where
  hashWithSalt :: Int -> ListTokens -> Int
hashWithSalt Int
_salt ListTokens' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
tokenIds :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
$sel:tokenIds:ListTokens' :: ListTokens -> Maybe [Text]
$sel:nextToken:ListTokens' :: ListTokens -> Maybe Text
$sel:maxResults:ListTokens' :: ListTokens -> Maybe Natural
$sel:filters:ListTokens' :: ListTokens -> Maybe [Filter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
tokenIds

instance Prelude.NFData ListTokens where
  rnf :: ListTokens -> ()
rnf ListTokens' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
tokenIds :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
$sel:tokenIds:ListTokens' :: ListTokens -> Maybe [Text]
$sel:nextToken:ListTokens' :: ListTokens -> Maybe Text
$sel:maxResults:ListTokens' :: ListTokens -> Maybe Natural
$sel:filters:ListTokens' :: ListTokens -> Maybe [Filter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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]
tokenIds

instance Data.ToHeaders ListTokens where
  toHeaders :: ListTokens -> 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
"AWSLicenseManager.ListTokens" ::
                          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 ListTokens where
  toJSON :: ListTokens -> Value
toJSON ListTokens' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
tokenIds :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
$sel:tokenIds:ListTokens' :: ListTokens -> Maybe [Text]
$sel:nextToken:ListTokens' :: ListTokens -> Maybe Text
$sel:maxResults:ListTokens' :: ListTokens -> Maybe Natural
$sel:filters:ListTokens' :: ListTokens -> Maybe [Filter]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 [Filter]
filters,
            (Key
"MaxResults" 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 Natural
maxResults,
            (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
"TokenIds" 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]
tokenIds
          ]
      )

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

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

-- | /See:/ 'newListTokensResponse' smart constructor.
data ListTokensResponse = ListTokensResponse'
  { -- | Token for the next set of results.
    ListTokensResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Received token details.
    ListTokensResponse -> Maybe [TokenData]
tokens :: Prelude.Maybe [TokenData],
    -- | The response's http status code.
    ListTokensResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListTokensResponse -> ListTokensResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTokensResponse -> ListTokensResponse -> Bool
$c/= :: ListTokensResponse -> ListTokensResponse -> Bool
== :: ListTokensResponse -> ListTokensResponse -> Bool
$c== :: ListTokensResponse -> ListTokensResponse -> Bool
Prelude.Eq, ReadPrec [ListTokensResponse]
ReadPrec ListTokensResponse
Int -> ReadS ListTokensResponse
ReadS [ListTokensResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTokensResponse]
$creadListPrec :: ReadPrec [ListTokensResponse]
readPrec :: ReadPrec ListTokensResponse
$creadPrec :: ReadPrec ListTokensResponse
readList :: ReadS [ListTokensResponse]
$creadList :: ReadS [ListTokensResponse]
readsPrec :: Int -> ReadS ListTokensResponse
$creadsPrec :: Int -> ReadS ListTokensResponse
Prelude.Read, Int -> ListTokensResponse -> ShowS
[ListTokensResponse] -> ShowS
ListTokensResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTokensResponse] -> ShowS
$cshowList :: [ListTokensResponse] -> ShowS
show :: ListTokensResponse -> String
$cshow :: ListTokensResponse -> String
showsPrec :: Int -> ListTokensResponse -> ShowS
$cshowsPrec :: Int -> ListTokensResponse -> ShowS
Prelude.Show, forall x. Rep ListTokensResponse x -> ListTokensResponse
forall x. ListTokensResponse -> Rep ListTokensResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTokensResponse x -> ListTokensResponse
$cfrom :: forall x. ListTokensResponse -> Rep ListTokensResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTokensResponse' 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', 'listTokensResponse_nextToken' - Token for the next set of results.
--
-- 'tokens', 'listTokensResponse_tokens' - Received token details.
--
-- 'httpStatus', 'listTokensResponse_httpStatus' - The response's http status code.
newListTokensResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTokensResponse
newListTokensResponse :: Int -> ListTokensResponse
newListTokensResponse Int
pHttpStatus_ =
  ListTokensResponse'
    { $sel:nextToken:ListTokensResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:tokens:ListTokensResponse' :: Maybe [TokenData]
tokens = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTokensResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Token for the next set of results.
listTokensResponse_nextToken :: Lens.Lens' ListTokensResponse (Prelude.Maybe Prelude.Text)
listTokensResponse_nextToken :: Lens' ListTokensResponse (Maybe Text)
listTokensResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTokensResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTokensResponse' :: ListTokensResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTokensResponse
s@ListTokensResponse' {} Maybe Text
a -> ListTokensResponse
s {$sel:nextToken:ListTokensResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListTokensResponse)

-- | Received token details.
listTokensResponse_tokens :: Lens.Lens' ListTokensResponse (Prelude.Maybe [TokenData])
listTokensResponse_tokens :: Lens' ListTokensResponse (Maybe [TokenData])
listTokensResponse_tokens = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTokensResponse' {Maybe [TokenData]
tokens :: Maybe [TokenData]
$sel:tokens:ListTokensResponse' :: ListTokensResponse -> Maybe [TokenData]
tokens} -> Maybe [TokenData]
tokens) (\s :: ListTokensResponse
s@ListTokensResponse' {} Maybe [TokenData]
a -> ListTokensResponse
s {$sel:tokens:ListTokensResponse' :: Maybe [TokenData]
tokens = Maybe [TokenData]
a} :: ListTokensResponse) 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.
listTokensResponse_httpStatus :: Lens.Lens' ListTokensResponse Prelude.Int
listTokensResponse_httpStatus :: Lens' ListTokensResponse Int
listTokensResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTokensResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListTokensResponse' :: ListTokensResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListTokensResponse
s@ListTokensResponse' {} Int
a -> ListTokensResponse
s {$sel:httpStatus:ListTokensResponse' :: Int
httpStatus = Int
a} :: ListTokensResponse)

instance Prelude.NFData ListTokensResponse where
  rnf :: ListTokensResponse -> ()
rnf ListTokensResponse' {Int
Maybe [TokenData]
Maybe Text
httpStatus :: Int
tokens :: Maybe [TokenData]
nextToken :: Maybe Text
$sel:httpStatus:ListTokensResponse' :: ListTokensResponse -> Int
$sel:tokens:ListTokensResponse' :: ListTokensResponse -> Maybe [TokenData]
$sel:nextToken:ListTokensResponse' :: ListTokensResponse -> 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 [TokenData]
tokens
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus