{-# 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.QLDB.ListLedgers
-- 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 an array of ledger summaries that are associated with the
-- current Amazon Web Services account and Region.
--
-- This action returns a maximum of 100 items and is paginated so that you
-- can retrieve all the items by calling @ListLedgers@ multiple times.
module Amazonka.QLDB.ListLedgers
  ( -- * Creating a Request
    ListLedgers (..),
    newListLedgers,

    -- * Request Lenses
    listLedgers_maxResults,
    listLedgers_nextToken,

    -- * Destructuring the Response
    ListLedgersResponse (..),
    newListLedgersResponse,

    -- * Response Lenses
    listLedgersResponse_ledgers,
    listLedgersResponse_nextToken,
    listLedgersResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListLedgers' smart constructor.
data ListLedgers = ListLedgers'
  { -- | The maximum number of results to return in a single @ListLedgers@
    -- request. (The actual number of results returned might be fewer.)
    ListLedgers -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A pagination token, indicating that you want to retrieve the next page
    -- of results. If you received a value for @NextToken@ in the response from
    -- a previous @ListLedgers@ call, then you should use that value as input
    -- here.
    ListLedgers -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListLedgers -> ListLedgers -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLedgers -> ListLedgers -> Bool
$c/= :: ListLedgers -> ListLedgers -> Bool
== :: ListLedgers -> ListLedgers -> Bool
$c== :: ListLedgers -> ListLedgers -> Bool
Prelude.Eq, ReadPrec [ListLedgers]
ReadPrec ListLedgers
Int -> ReadS ListLedgers
ReadS [ListLedgers]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLedgers]
$creadListPrec :: ReadPrec [ListLedgers]
readPrec :: ReadPrec ListLedgers
$creadPrec :: ReadPrec ListLedgers
readList :: ReadS [ListLedgers]
$creadList :: ReadS [ListLedgers]
readsPrec :: Int -> ReadS ListLedgers
$creadsPrec :: Int -> ReadS ListLedgers
Prelude.Read, Int -> ListLedgers -> ShowS
[ListLedgers] -> ShowS
ListLedgers -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLedgers] -> ShowS
$cshowList :: [ListLedgers] -> ShowS
show :: ListLedgers -> String
$cshow :: ListLedgers -> String
showsPrec :: Int -> ListLedgers -> ShowS
$cshowsPrec :: Int -> ListLedgers -> ShowS
Prelude.Show, forall x. Rep ListLedgers x -> ListLedgers
forall x. ListLedgers -> Rep ListLedgers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLedgers x -> ListLedgers
$cfrom :: forall x. ListLedgers -> Rep ListLedgers x
Prelude.Generic)

-- |
-- Create a value of 'ListLedgers' 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:
--
-- 'maxResults', 'listLedgers_maxResults' - The maximum number of results to return in a single @ListLedgers@
-- request. (The actual number of results returned might be fewer.)
--
-- 'nextToken', 'listLedgers_nextToken' - A pagination token, indicating that you want to retrieve the next page
-- of results. If you received a value for @NextToken@ in the response from
-- a previous @ListLedgers@ call, then you should use that value as input
-- here.
newListLedgers ::
  ListLedgers
newListLedgers :: ListLedgers
newListLedgers =
  ListLedgers'
    { $sel:maxResults:ListLedgers' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLedgers' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to return in a single @ListLedgers@
-- request. (The actual number of results returned might be fewer.)
listLedgers_maxResults :: Lens.Lens' ListLedgers (Prelude.Maybe Prelude.Natural)
listLedgers_maxResults :: Lens' ListLedgers (Maybe Natural)
listLedgers_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLedgers' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListLedgers' :: ListLedgers -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListLedgers
s@ListLedgers' {} Maybe Natural
a -> ListLedgers
s {$sel:maxResults:ListLedgers' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListLedgers)

-- | A pagination token, indicating that you want to retrieve the next page
-- of results. If you received a value for @NextToken@ in the response from
-- a previous @ListLedgers@ call, then you should use that value as input
-- here.
listLedgers_nextToken :: Lens.Lens' ListLedgers (Prelude.Maybe Prelude.Text)
listLedgers_nextToken :: Lens' ListLedgers (Maybe Text)
listLedgers_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLedgers' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListLedgers' :: ListLedgers -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListLedgers
s@ListLedgers' {} Maybe Text
a -> ListLedgers
s {$sel:nextToken:ListLedgers' :: Maybe Text
nextToken = Maybe Text
a} :: ListLedgers)

instance Core.AWSRequest ListLedgers where
  type AWSResponse ListLedgers = ListLedgersResponse
  request :: (Service -> Service) -> ListLedgers -> Request ListLedgers
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListLedgers
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListLedgers)))
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 [LedgerSummary] -> Maybe Text -> Int -> ListLedgersResponse
ListLedgersResponse'
            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
"Ledgers" 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.<*> (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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListLedgers where
  hashWithSalt :: Int -> ListLedgers -> Int
hashWithSalt Int
_salt ListLedgers' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListLedgers' :: ListLedgers -> Maybe Text
$sel:maxResults:ListLedgers' :: ListLedgers -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListLedgers where
  rnf :: ListLedgers -> ()
rnf ListLedgers' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListLedgers' :: ListLedgers -> Maybe Text
$sel:maxResults:ListLedgers' :: ListLedgers -> Maybe Natural
..} =
    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

instance Data.ToHeaders ListLedgers where
  toHeaders :: ListLedgers -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

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

instance Data.ToQuery ListLedgers where
  toQuery :: ListLedgers -> QueryString
toQuery ListLedgers' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListLedgers' :: ListLedgers -> Maybe Text
$sel:maxResults:ListLedgers' :: ListLedgers -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"max_results" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"next_token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListLedgersResponse' smart constructor.
data ListLedgersResponse = ListLedgersResponse'
  { -- | The array of ledger summaries that are associated with the current
    -- Amazon Web Services account and Region.
    ListLedgersResponse -> Maybe [LedgerSummary]
ledgers :: Prelude.Maybe [LedgerSummary],
    -- | A pagination token, indicating whether there are more results available:
    --
    -- -   If @NextToken@ is empty, then the last page of results has been
    --     processed and there are no more results to be retrieved.
    --
    -- -   If @NextToken@ is /not/ empty, then there are more results
    --     available. To retrieve the next page of results, use the value of
    --     @NextToken@ in a subsequent @ListLedgers@ call.
    ListLedgersResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListLedgersResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListLedgersResponse -> ListLedgersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLedgersResponse -> ListLedgersResponse -> Bool
$c/= :: ListLedgersResponse -> ListLedgersResponse -> Bool
== :: ListLedgersResponse -> ListLedgersResponse -> Bool
$c== :: ListLedgersResponse -> ListLedgersResponse -> Bool
Prelude.Eq, ReadPrec [ListLedgersResponse]
ReadPrec ListLedgersResponse
Int -> ReadS ListLedgersResponse
ReadS [ListLedgersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLedgersResponse]
$creadListPrec :: ReadPrec [ListLedgersResponse]
readPrec :: ReadPrec ListLedgersResponse
$creadPrec :: ReadPrec ListLedgersResponse
readList :: ReadS [ListLedgersResponse]
$creadList :: ReadS [ListLedgersResponse]
readsPrec :: Int -> ReadS ListLedgersResponse
$creadsPrec :: Int -> ReadS ListLedgersResponse
Prelude.Read, Int -> ListLedgersResponse -> ShowS
[ListLedgersResponse] -> ShowS
ListLedgersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLedgersResponse] -> ShowS
$cshowList :: [ListLedgersResponse] -> ShowS
show :: ListLedgersResponse -> String
$cshow :: ListLedgersResponse -> String
showsPrec :: Int -> ListLedgersResponse -> ShowS
$cshowsPrec :: Int -> ListLedgersResponse -> ShowS
Prelude.Show, forall x. Rep ListLedgersResponse x -> ListLedgersResponse
forall x. ListLedgersResponse -> Rep ListLedgersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLedgersResponse x -> ListLedgersResponse
$cfrom :: forall x. ListLedgersResponse -> Rep ListLedgersResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListLedgersResponse' 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:
--
-- 'ledgers', 'listLedgersResponse_ledgers' - The array of ledger summaries that are associated with the current
-- Amazon Web Services account and Region.
--
-- 'nextToken', 'listLedgersResponse_nextToken' - A pagination token, indicating whether there are more results available:
--
-- -   If @NextToken@ is empty, then the last page of results has been
--     processed and there are no more results to be retrieved.
--
-- -   If @NextToken@ is /not/ empty, then there are more results
--     available. To retrieve the next page of results, use the value of
--     @NextToken@ in a subsequent @ListLedgers@ call.
--
-- 'httpStatus', 'listLedgersResponse_httpStatus' - The response's http status code.
newListLedgersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListLedgersResponse
newListLedgersResponse :: Int -> ListLedgersResponse
newListLedgersResponse Int
pHttpStatus_ =
  ListLedgersResponse'
    { $sel:ledgers:ListLedgersResponse' :: Maybe [LedgerSummary]
ledgers = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLedgersResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListLedgersResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The array of ledger summaries that are associated with the current
-- Amazon Web Services account and Region.
listLedgersResponse_ledgers :: Lens.Lens' ListLedgersResponse (Prelude.Maybe [LedgerSummary])
listLedgersResponse_ledgers :: Lens' ListLedgersResponse (Maybe [LedgerSummary])
listLedgersResponse_ledgers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLedgersResponse' {Maybe [LedgerSummary]
ledgers :: Maybe [LedgerSummary]
$sel:ledgers:ListLedgersResponse' :: ListLedgersResponse -> Maybe [LedgerSummary]
ledgers} -> Maybe [LedgerSummary]
ledgers) (\s :: ListLedgersResponse
s@ListLedgersResponse' {} Maybe [LedgerSummary]
a -> ListLedgersResponse
s {$sel:ledgers:ListLedgersResponse' :: Maybe [LedgerSummary]
ledgers = Maybe [LedgerSummary]
a} :: ListLedgersResponse) 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

-- | A pagination token, indicating whether there are more results available:
--
-- -   If @NextToken@ is empty, then the last page of results has been
--     processed and there are no more results to be retrieved.
--
-- -   If @NextToken@ is /not/ empty, then there are more results
--     available. To retrieve the next page of results, use the value of
--     @NextToken@ in a subsequent @ListLedgers@ call.
listLedgersResponse_nextToken :: Lens.Lens' ListLedgersResponse (Prelude.Maybe Prelude.Text)
listLedgersResponse_nextToken :: Lens' ListLedgersResponse (Maybe Text)
listLedgersResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLedgersResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListLedgersResponse' :: ListLedgersResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListLedgersResponse
s@ListLedgersResponse' {} Maybe Text
a -> ListLedgersResponse
s {$sel:nextToken:ListLedgersResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListLedgersResponse)

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

instance Prelude.NFData ListLedgersResponse where
  rnf :: ListLedgersResponse -> ()
rnf ListLedgersResponse' {Int
Maybe [LedgerSummary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
ledgers :: Maybe [LedgerSummary]
$sel:httpStatus:ListLedgersResponse' :: ListLedgersResponse -> Int
$sel:nextToken:ListLedgersResponse' :: ListLedgersResponse -> Maybe Text
$sel:ledgers:ListLedgersResponse' :: ListLedgersResponse -> Maybe [LedgerSummary]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LedgerSummary]
ledgers
      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 Int
httpStatus