{-# 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.GroundStation.ListConfigs
-- 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 @Config@ objects.
--
-- This operation returns paginated results.
module Amazonka.GroundStation.ListConfigs
  ( -- * Creating a Request
    ListConfigs (..),
    newListConfigs,

    -- * Request Lenses
    listConfigs_maxResults,
    listConfigs_nextToken,

    -- * Destructuring the Response
    ListConfigsResponse (..),
    newListConfigsResponse,

    -- * Response Lenses
    listConfigsResponse_configList,
    listConfigsResponse_nextToken,
    listConfigsResponse_httpStatus,
  )
where

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

-- |
--
-- /See:/ 'newListConfigs' smart constructor.
data ListConfigs = ListConfigs'
  { -- | Maximum number of @Configs@ returned.
    ListConfigs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Next token returned in the request of a previous @ListConfigs@ call.
    -- Used to get the next page of results.
    ListConfigs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListConfigs -> ListConfigs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConfigs -> ListConfigs -> Bool
$c/= :: ListConfigs -> ListConfigs -> Bool
== :: ListConfigs -> ListConfigs -> Bool
$c== :: ListConfigs -> ListConfigs -> Bool
Prelude.Eq, ReadPrec [ListConfigs]
ReadPrec ListConfigs
Int -> ReadS ListConfigs
ReadS [ListConfigs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConfigs]
$creadListPrec :: ReadPrec [ListConfigs]
readPrec :: ReadPrec ListConfigs
$creadPrec :: ReadPrec ListConfigs
readList :: ReadS [ListConfigs]
$creadList :: ReadS [ListConfigs]
readsPrec :: Int -> ReadS ListConfigs
$creadsPrec :: Int -> ReadS ListConfigs
Prelude.Read, Int -> ListConfigs -> ShowS
[ListConfigs] -> ShowS
ListConfigs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConfigs] -> ShowS
$cshowList :: [ListConfigs] -> ShowS
show :: ListConfigs -> String
$cshow :: ListConfigs -> String
showsPrec :: Int -> ListConfigs -> ShowS
$cshowsPrec :: Int -> ListConfigs -> ShowS
Prelude.Show, forall x. Rep ListConfigs x -> ListConfigs
forall x. ListConfigs -> Rep ListConfigs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListConfigs x -> ListConfigs
$cfrom :: forall x. ListConfigs -> Rep ListConfigs x
Prelude.Generic)

-- |
-- Create a value of 'ListConfigs' 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', 'listConfigs_maxResults' - Maximum number of @Configs@ returned.
--
-- 'nextToken', 'listConfigs_nextToken' - Next token returned in the request of a previous @ListConfigs@ call.
-- Used to get the next page of results.
newListConfigs ::
  ListConfigs
newListConfigs :: ListConfigs
newListConfigs =
  ListConfigs'
    { $sel:maxResults:ListConfigs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConfigs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Maximum number of @Configs@ returned.
listConfigs_maxResults :: Lens.Lens' ListConfigs (Prelude.Maybe Prelude.Natural)
listConfigs_maxResults :: Lens' ListConfigs (Maybe Natural)
listConfigs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListConfigs' :: ListConfigs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListConfigs
s@ListConfigs' {} Maybe Natural
a -> ListConfigs
s {$sel:maxResults:ListConfigs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListConfigs)

-- | Next token returned in the request of a previous @ListConfigs@ call.
-- Used to get the next page of results.
listConfigs_nextToken :: Lens.Lens' ListConfigs (Prelude.Maybe Prelude.Text)
listConfigs_nextToken :: Lens' ListConfigs (Maybe Text)
listConfigs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConfigs' :: ListConfigs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConfigs
s@ListConfigs' {} Maybe Text
a -> ListConfigs
s {$sel:nextToken:ListConfigs' :: Maybe Text
nextToken = Maybe Text
a} :: ListConfigs)

instance Core.AWSPager ListConfigs where
  page :: ListConfigs -> AWSResponse ListConfigs -> Maybe ListConfigs
page ListConfigs
rq AWSResponse ListConfigs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListConfigs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigsResponse (Maybe Text)
listConfigsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListConfigs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigsResponse (Maybe [ConfigListItem])
listConfigsResponse_configList
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListConfigs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListConfigs (Maybe Text)
listConfigs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListConfigs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigsResponse (Maybe Text)
listConfigsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListConfigs where
  type AWSResponse ListConfigs = ListConfigsResponse
  request :: (Service -> Service) -> ListConfigs -> Request ListConfigs
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 ListConfigs
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListConfigs)))
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 [ConfigListItem] -> Maybe Text -> Int -> ListConfigsResponse
ListConfigsResponse'
            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
"configList" 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 ListConfigs where
  hashWithSalt :: Int -> ListConfigs -> Int
hashWithSalt Int
_salt ListConfigs' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListConfigs' :: ListConfigs -> Maybe Text
$sel:maxResults:ListConfigs' :: ListConfigs -> 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 ListConfigs where
  rnf :: ListConfigs -> ()
rnf ListConfigs' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListConfigs' :: ListConfigs -> Maybe Text
$sel:maxResults:ListConfigs' :: ListConfigs -> 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 ListConfigs where
  toHeaders :: ListConfigs -> 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.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

-- |
--
-- /See:/ 'newListConfigsResponse' smart constructor.
data ListConfigsResponse = ListConfigsResponse'
  { -- | List of @Config@ items.
    ListConfigsResponse -> Maybe [ConfigListItem]
configList :: Prelude.Maybe [ConfigListItem],
    -- | Next token returned in the response of a previous @ListConfigs@ call.
    -- Used to get the next page of results.
    ListConfigsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListConfigsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListConfigsResponse -> ListConfigsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConfigsResponse -> ListConfigsResponse -> Bool
$c/= :: ListConfigsResponse -> ListConfigsResponse -> Bool
== :: ListConfigsResponse -> ListConfigsResponse -> Bool
$c== :: ListConfigsResponse -> ListConfigsResponse -> Bool
Prelude.Eq, ReadPrec [ListConfigsResponse]
ReadPrec ListConfigsResponse
Int -> ReadS ListConfigsResponse
ReadS [ListConfigsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConfigsResponse]
$creadListPrec :: ReadPrec [ListConfigsResponse]
readPrec :: ReadPrec ListConfigsResponse
$creadPrec :: ReadPrec ListConfigsResponse
readList :: ReadS [ListConfigsResponse]
$creadList :: ReadS [ListConfigsResponse]
readsPrec :: Int -> ReadS ListConfigsResponse
$creadsPrec :: Int -> ReadS ListConfigsResponse
Prelude.Read, Int -> ListConfigsResponse -> ShowS
[ListConfigsResponse] -> ShowS
ListConfigsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConfigsResponse] -> ShowS
$cshowList :: [ListConfigsResponse] -> ShowS
show :: ListConfigsResponse -> String
$cshow :: ListConfigsResponse -> String
showsPrec :: Int -> ListConfigsResponse -> ShowS
$cshowsPrec :: Int -> ListConfigsResponse -> ShowS
Prelude.Show, forall x. Rep ListConfigsResponse x -> ListConfigsResponse
forall x. ListConfigsResponse -> Rep ListConfigsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListConfigsResponse x -> ListConfigsResponse
$cfrom :: forall x. ListConfigsResponse -> Rep ListConfigsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListConfigsResponse' 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:
--
-- 'configList', 'listConfigsResponse_configList' - List of @Config@ items.
--
-- 'nextToken', 'listConfigsResponse_nextToken' - Next token returned in the response of a previous @ListConfigs@ call.
-- Used to get the next page of results.
--
-- 'httpStatus', 'listConfigsResponse_httpStatus' - The response's http status code.
newListConfigsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListConfigsResponse
newListConfigsResponse :: Int -> ListConfigsResponse
newListConfigsResponse Int
pHttpStatus_ =
  ListConfigsResponse'
    { $sel:configList:ListConfigsResponse' :: Maybe [ConfigListItem]
configList = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConfigsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListConfigsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | List of @Config@ items.
listConfigsResponse_configList :: Lens.Lens' ListConfigsResponse (Prelude.Maybe [ConfigListItem])
listConfigsResponse_configList :: Lens' ListConfigsResponse (Maybe [ConfigListItem])
listConfigsResponse_configList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigsResponse' {Maybe [ConfigListItem]
configList :: Maybe [ConfigListItem]
$sel:configList:ListConfigsResponse' :: ListConfigsResponse -> Maybe [ConfigListItem]
configList} -> Maybe [ConfigListItem]
configList) (\s :: ListConfigsResponse
s@ListConfigsResponse' {} Maybe [ConfigListItem]
a -> ListConfigsResponse
s {$sel:configList:ListConfigsResponse' :: Maybe [ConfigListItem]
configList = Maybe [ConfigListItem]
a} :: ListConfigsResponse) 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

-- | Next token returned in the response of a previous @ListConfigs@ call.
-- Used to get the next page of results.
listConfigsResponse_nextToken :: Lens.Lens' ListConfigsResponse (Prelude.Maybe Prelude.Text)
listConfigsResponse_nextToken :: Lens' ListConfigsResponse (Maybe Text)
listConfigsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConfigsResponse' :: ListConfigsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConfigsResponse
s@ListConfigsResponse' {} Maybe Text
a -> ListConfigsResponse
s {$sel:nextToken:ListConfigsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListConfigsResponse)

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

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