{-# 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.GlobalAccelerator.ListAccelerators
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- List the accelerators for an Amazon Web Services account.
--
-- This operation returns paginated results.
module Amazonka.GlobalAccelerator.ListAccelerators
  ( -- * Creating a Request
    ListAccelerators (..),
    newListAccelerators,

    -- * Request Lenses
    listAccelerators_maxResults,
    listAccelerators_nextToken,

    -- * Destructuring the Response
    ListAcceleratorsResponse (..),
    newListAcceleratorsResponse,

    -- * Response Lenses
    listAcceleratorsResponse_accelerators,
    listAcceleratorsResponse_nextToken,
    listAcceleratorsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListAccelerators' smart constructor.
data ListAccelerators = ListAccelerators'
  { -- | The number of Global Accelerator objects that you want to return with
    -- this call. The default value is 10.
    ListAccelerators -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next set of results. You receive this token from a
    -- previous call.
    ListAccelerators -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListAccelerators -> ListAccelerators -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAccelerators -> ListAccelerators -> Bool
$c/= :: ListAccelerators -> ListAccelerators -> Bool
== :: ListAccelerators -> ListAccelerators -> Bool
$c== :: ListAccelerators -> ListAccelerators -> Bool
Prelude.Eq, ReadPrec [ListAccelerators]
ReadPrec ListAccelerators
Int -> ReadS ListAccelerators
ReadS [ListAccelerators]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAccelerators]
$creadListPrec :: ReadPrec [ListAccelerators]
readPrec :: ReadPrec ListAccelerators
$creadPrec :: ReadPrec ListAccelerators
readList :: ReadS [ListAccelerators]
$creadList :: ReadS [ListAccelerators]
readsPrec :: Int -> ReadS ListAccelerators
$creadsPrec :: Int -> ReadS ListAccelerators
Prelude.Read, Int -> ListAccelerators -> ShowS
[ListAccelerators] -> ShowS
ListAccelerators -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAccelerators] -> ShowS
$cshowList :: [ListAccelerators] -> ShowS
show :: ListAccelerators -> String
$cshow :: ListAccelerators -> String
showsPrec :: Int -> ListAccelerators -> ShowS
$cshowsPrec :: Int -> ListAccelerators -> ShowS
Prelude.Show, forall x. Rep ListAccelerators x -> ListAccelerators
forall x. ListAccelerators -> Rep ListAccelerators x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAccelerators x -> ListAccelerators
$cfrom :: forall x. ListAccelerators -> Rep ListAccelerators x
Prelude.Generic)

-- |
-- Create a value of 'ListAccelerators' 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', 'listAccelerators_maxResults' - The number of Global Accelerator objects that you want to return with
-- this call. The default value is 10.
--
-- 'nextToken', 'listAccelerators_nextToken' - The token for the next set of results. You receive this token from a
-- previous call.
newListAccelerators ::
  ListAccelerators
newListAccelerators :: ListAccelerators
newListAccelerators =
  ListAccelerators'
    { $sel:maxResults:ListAccelerators' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAccelerators' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The number of Global Accelerator objects that you want to return with
-- this call. The default value is 10.
listAccelerators_maxResults :: Lens.Lens' ListAccelerators (Prelude.Maybe Prelude.Natural)
listAccelerators_maxResults :: Lens' ListAccelerators (Maybe Natural)
listAccelerators_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAccelerators' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAccelerators' :: ListAccelerators -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAccelerators
s@ListAccelerators' {} Maybe Natural
a -> ListAccelerators
s {$sel:maxResults:ListAccelerators' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAccelerators)

-- | The token for the next set of results. You receive this token from a
-- previous call.
listAccelerators_nextToken :: Lens.Lens' ListAccelerators (Prelude.Maybe Prelude.Text)
listAccelerators_nextToken :: Lens' ListAccelerators (Maybe Text)
listAccelerators_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAccelerators' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAccelerators' :: ListAccelerators -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAccelerators
s@ListAccelerators' {} Maybe Text
a -> ListAccelerators
s {$sel:nextToken:ListAccelerators' :: Maybe Text
nextToken = Maybe Text
a} :: ListAccelerators)

instance Core.AWSPager ListAccelerators where
  page :: ListAccelerators
-> AWSResponse ListAccelerators -> Maybe ListAccelerators
page ListAccelerators
rq AWSResponse ListAccelerators
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAccelerators
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAcceleratorsResponse (Maybe Text)
listAcceleratorsResponse_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 ListAccelerators
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAcceleratorsResponse (Maybe [Accelerator])
listAcceleratorsResponse_accelerators
            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.$ ListAccelerators
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAccelerators (Maybe Text)
listAccelerators_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAccelerators
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAcceleratorsResponse (Maybe Text)
listAcceleratorsResponse_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 ListAccelerators where
  type
    AWSResponse ListAccelerators =
      ListAcceleratorsResponse
  request :: (Service -> Service)
-> ListAccelerators -> Request ListAccelerators
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 ListAccelerators
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListAccelerators)))
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 [Accelerator]
-> Maybe Text -> Int -> ListAcceleratorsResponse
ListAcceleratorsResponse'
            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
"Accelerators" 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 ListAccelerators where
  hashWithSalt :: Int -> ListAccelerators -> Int
hashWithSalt Int
_salt ListAccelerators' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListAccelerators' :: ListAccelerators -> Maybe Text
$sel:maxResults:ListAccelerators' :: ListAccelerators -> 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 ListAccelerators where
  rnf :: ListAccelerators -> ()
rnf ListAccelerators' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListAccelerators' :: ListAccelerators -> Maybe Text
$sel:maxResults:ListAccelerators' :: ListAccelerators -> 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 ListAccelerators where
  toHeaders :: ListAccelerators -> 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
"GlobalAccelerator_V20180706.ListAccelerators" ::
                          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 ListAccelerators where
  toJSON :: ListAccelerators -> Value
toJSON ListAccelerators' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListAccelerators' :: ListAccelerators -> Maybe Text
$sel:maxResults:ListAccelerators' :: ListAccelerators -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
          ]
      )

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

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

-- | /See:/ 'newListAcceleratorsResponse' smart constructor.
data ListAcceleratorsResponse = ListAcceleratorsResponse'
  { -- | The list of accelerators for a customer account.
    ListAcceleratorsResponse -> Maybe [Accelerator]
accelerators :: Prelude.Maybe [Accelerator],
    -- | The token for the next set of results. You receive this token from a
    -- previous call.
    ListAcceleratorsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAcceleratorsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAcceleratorsResponse -> ListAcceleratorsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAcceleratorsResponse -> ListAcceleratorsResponse -> Bool
$c/= :: ListAcceleratorsResponse -> ListAcceleratorsResponse -> Bool
== :: ListAcceleratorsResponse -> ListAcceleratorsResponse -> Bool
$c== :: ListAcceleratorsResponse -> ListAcceleratorsResponse -> Bool
Prelude.Eq, ReadPrec [ListAcceleratorsResponse]
ReadPrec ListAcceleratorsResponse
Int -> ReadS ListAcceleratorsResponse
ReadS [ListAcceleratorsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAcceleratorsResponse]
$creadListPrec :: ReadPrec [ListAcceleratorsResponse]
readPrec :: ReadPrec ListAcceleratorsResponse
$creadPrec :: ReadPrec ListAcceleratorsResponse
readList :: ReadS [ListAcceleratorsResponse]
$creadList :: ReadS [ListAcceleratorsResponse]
readsPrec :: Int -> ReadS ListAcceleratorsResponse
$creadsPrec :: Int -> ReadS ListAcceleratorsResponse
Prelude.Read, Int -> ListAcceleratorsResponse -> ShowS
[ListAcceleratorsResponse] -> ShowS
ListAcceleratorsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAcceleratorsResponse] -> ShowS
$cshowList :: [ListAcceleratorsResponse] -> ShowS
show :: ListAcceleratorsResponse -> String
$cshow :: ListAcceleratorsResponse -> String
showsPrec :: Int -> ListAcceleratorsResponse -> ShowS
$cshowsPrec :: Int -> ListAcceleratorsResponse -> ShowS
Prelude.Show, forall x.
Rep ListAcceleratorsResponse x -> ListAcceleratorsResponse
forall x.
ListAcceleratorsResponse -> Rep ListAcceleratorsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAcceleratorsResponse x -> ListAcceleratorsResponse
$cfrom :: forall x.
ListAcceleratorsResponse -> Rep ListAcceleratorsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAcceleratorsResponse' 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:
--
-- 'accelerators', 'listAcceleratorsResponse_accelerators' - The list of accelerators for a customer account.
--
-- 'nextToken', 'listAcceleratorsResponse_nextToken' - The token for the next set of results. You receive this token from a
-- previous call.
--
-- 'httpStatus', 'listAcceleratorsResponse_httpStatus' - The response's http status code.
newListAcceleratorsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAcceleratorsResponse
newListAcceleratorsResponse :: Int -> ListAcceleratorsResponse
newListAcceleratorsResponse Int
pHttpStatus_ =
  ListAcceleratorsResponse'
    { $sel:accelerators:ListAcceleratorsResponse' :: Maybe [Accelerator]
accelerators =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAcceleratorsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAcceleratorsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of accelerators for a customer account.
listAcceleratorsResponse_accelerators :: Lens.Lens' ListAcceleratorsResponse (Prelude.Maybe [Accelerator])
listAcceleratorsResponse_accelerators :: Lens' ListAcceleratorsResponse (Maybe [Accelerator])
listAcceleratorsResponse_accelerators = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAcceleratorsResponse' {Maybe [Accelerator]
accelerators :: Maybe [Accelerator]
$sel:accelerators:ListAcceleratorsResponse' :: ListAcceleratorsResponse -> Maybe [Accelerator]
accelerators} -> Maybe [Accelerator]
accelerators) (\s :: ListAcceleratorsResponse
s@ListAcceleratorsResponse' {} Maybe [Accelerator]
a -> ListAcceleratorsResponse
s {$sel:accelerators:ListAcceleratorsResponse' :: Maybe [Accelerator]
accelerators = Maybe [Accelerator]
a} :: ListAcceleratorsResponse) 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 token for the next set of results. You receive this token from a
-- previous call.
listAcceleratorsResponse_nextToken :: Lens.Lens' ListAcceleratorsResponse (Prelude.Maybe Prelude.Text)
listAcceleratorsResponse_nextToken :: Lens' ListAcceleratorsResponse (Maybe Text)
listAcceleratorsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAcceleratorsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAcceleratorsResponse' :: ListAcceleratorsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAcceleratorsResponse
s@ListAcceleratorsResponse' {} Maybe Text
a -> ListAcceleratorsResponse
s {$sel:nextToken:ListAcceleratorsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAcceleratorsResponse)

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

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