{-# 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.AppSync.ListGraphqlApis
-- 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 GraphQL APIs.
--
-- This operation returns paginated results.
module Amazonka.AppSync.ListGraphqlApis
  ( -- * Creating a Request
    ListGraphqlApis (..),
    newListGraphqlApis,

    -- * Request Lenses
    listGraphqlApis_maxResults,
    listGraphqlApis_nextToken,

    -- * Destructuring the Response
    ListGraphqlApisResponse (..),
    newListGraphqlApisResponse,

    -- * Response Lenses
    listGraphqlApisResponse_graphqlApis,
    listGraphqlApisResponse_nextToken,
    listGraphqlApisResponse_httpStatus,
  )
where

import Amazonka.AppSync.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListGraphqlApis' smart constructor.
data ListGraphqlApis = ListGraphqlApis'
  { -- | The maximum number of results that you want the request to return.
    ListGraphqlApis -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | An identifier that was returned from the previous call to this
    -- operation, which you can use to return the next set of items in the
    -- list.
    ListGraphqlApis -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListGraphqlApis -> ListGraphqlApis -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListGraphqlApis -> ListGraphqlApis -> Bool
$c/= :: ListGraphqlApis -> ListGraphqlApis -> Bool
== :: ListGraphqlApis -> ListGraphqlApis -> Bool
$c== :: ListGraphqlApis -> ListGraphqlApis -> Bool
Prelude.Eq, ReadPrec [ListGraphqlApis]
ReadPrec ListGraphqlApis
Int -> ReadS ListGraphqlApis
ReadS [ListGraphqlApis]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListGraphqlApis]
$creadListPrec :: ReadPrec [ListGraphqlApis]
readPrec :: ReadPrec ListGraphqlApis
$creadPrec :: ReadPrec ListGraphqlApis
readList :: ReadS [ListGraphqlApis]
$creadList :: ReadS [ListGraphqlApis]
readsPrec :: Int -> ReadS ListGraphqlApis
$creadsPrec :: Int -> ReadS ListGraphqlApis
Prelude.Read, Int -> ListGraphqlApis -> ShowS
[ListGraphqlApis] -> ShowS
ListGraphqlApis -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListGraphqlApis] -> ShowS
$cshowList :: [ListGraphqlApis] -> ShowS
show :: ListGraphqlApis -> String
$cshow :: ListGraphqlApis -> String
showsPrec :: Int -> ListGraphqlApis -> ShowS
$cshowsPrec :: Int -> ListGraphqlApis -> ShowS
Prelude.Show, forall x. Rep ListGraphqlApis x -> ListGraphqlApis
forall x. ListGraphqlApis -> Rep ListGraphqlApis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListGraphqlApis x -> ListGraphqlApis
$cfrom :: forall x. ListGraphqlApis -> Rep ListGraphqlApis x
Prelude.Generic)

-- |
-- Create a value of 'ListGraphqlApis' 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', 'listGraphqlApis_maxResults' - The maximum number of results that you want the request to return.
--
-- 'nextToken', 'listGraphqlApis_nextToken' - An identifier that was returned from the previous call to this
-- operation, which you can use to return the next set of items in the
-- list.
newListGraphqlApis ::
  ListGraphqlApis
newListGraphqlApis :: ListGraphqlApis
newListGraphqlApis =
  ListGraphqlApis'
    { $sel:maxResults:ListGraphqlApis' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListGraphqlApis' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results that you want the request to return.
listGraphqlApis_maxResults :: Lens.Lens' ListGraphqlApis (Prelude.Maybe Prelude.Natural)
listGraphqlApis_maxResults :: Lens' ListGraphqlApis (Maybe Natural)
listGraphqlApis_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGraphqlApis' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListGraphqlApis' :: ListGraphqlApis -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListGraphqlApis
s@ListGraphqlApis' {} Maybe Natural
a -> ListGraphqlApis
s {$sel:maxResults:ListGraphqlApis' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListGraphqlApis)

-- | An identifier that was returned from the previous call to this
-- operation, which you can use to return the next set of items in the
-- list.
listGraphqlApis_nextToken :: Lens.Lens' ListGraphqlApis (Prelude.Maybe Prelude.Text)
listGraphqlApis_nextToken :: Lens' ListGraphqlApis (Maybe Text)
listGraphqlApis_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGraphqlApis' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListGraphqlApis' :: ListGraphqlApis -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListGraphqlApis
s@ListGraphqlApis' {} Maybe Text
a -> ListGraphqlApis
s {$sel:nextToken:ListGraphqlApis' :: Maybe Text
nextToken = Maybe Text
a} :: ListGraphqlApis)

instance Core.AWSPager ListGraphqlApis where
  page :: ListGraphqlApis
-> AWSResponse ListGraphqlApis -> Maybe ListGraphqlApis
page ListGraphqlApis
rq AWSResponse ListGraphqlApis
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListGraphqlApis
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListGraphqlApisResponse (Maybe Text)
listGraphqlApisResponse_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 ListGraphqlApis
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListGraphqlApisResponse (Maybe [GraphqlApi])
listGraphqlApisResponse_graphqlApis
            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.$ ListGraphqlApis
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListGraphqlApis (Maybe Text)
listGraphqlApis_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListGraphqlApis
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListGraphqlApisResponse (Maybe Text)
listGraphqlApisResponse_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 ListGraphqlApis where
  type
    AWSResponse ListGraphqlApis =
      ListGraphqlApisResponse
  request :: (Service -> Service) -> ListGraphqlApis -> Request ListGraphqlApis
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 ListGraphqlApis
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListGraphqlApis)))
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 [GraphqlApi] -> Maybe Text -> Int -> ListGraphqlApisResponse
ListGraphqlApisResponse'
            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
"graphqlApis" 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 ListGraphqlApis where
  hashWithSalt :: Int -> ListGraphqlApis -> Int
hashWithSalt Int
_salt ListGraphqlApis' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListGraphqlApis' :: ListGraphqlApis -> Maybe Text
$sel:maxResults:ListGraphqlApis' :: ListGraphqlApis -> 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 ListGraphqlApis where
  rnf :: ListGraphqlApis -> ()
rnf ListGraphqlApis' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListGraphqlApis' :: ListGraphqlApis -> Maybe Text
$sel:maxResults:ListGraphqlApis' :: ListGraphqlApis -> 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 ListGraphqlApis where
  toHeaders :: ListGraphqlApis -> 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 ListGraphqlApis where
  toPath :: ListGraphqlApis -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/apis"

instance Data.ToQuery ListGraphqlApis where
  toQuery :: ListGraphqlApis -> QueryString
toQuery ListGraphqlApis' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListGraphqlApis' :: ListGraphqlApis -> Maybe Text
$sel:maxResults:ListGraphqlApis' :: ListGraphqlApis -> 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:/ 'newListGraphqlApisResponse' smart constructor.
data ListGraphqlApisResponse = ListGraphqlApisResponse'
  { -- | The @GraphqlApi@ objects.
    ListGraphqlApisResponse -> Maybe [GraphqlApi]
graphqlApis :: Prelude.Maybe [GraphqlApi],
    -- | An identifier to pass in the next request to this operation to return
    -- the next set of items in the list.
    ListGraphqlApisResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListGraphqlApisResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListGraphqlApisResponse -> ListGraphqlApisResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListGraphqlApisResponse -> ListGraphqlApisResponse -> Bool
$c/= :: ListGraphqlApisResponse -> ListGraphqlApisResponse -> Bool
== :: ListGraphqlApisResponse -> ListGraphqlApisResponse -> Bool
$c== :: ListGraphqlApisResponse -> ListGraphqlApisResponse -> Bool
Prelude.Eq, ReadPrec [ListGraphqlApisResponse]
ReadPrec ListGraphqlApisResponse
Int -> ReadS ListGraphqlApisResponse
ReadS [ListGraphqlApisResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListGraphqlApisResponse]
$creadListPrec :: ReadPrec [ListGraphqlApisResponse]
readPrec :: ReadPrec ListGraphqlApisResponse
$creadPrec :: ReadPrec ListGraphqlApisResponse
readList :: ReadS [ListGraphqlApisResponse]
$creadList :: ReadS [ListGraphqlApisResponse]
readsPrec :: Int -> ReadS ListGraphqlApisResponse
$creadsPrec :: Int -> ReadS ListGraphqlApisResponse
Prelude.Read, Int -> ListGraphqlApisResponse -> ShowS
[ListGraphqlApisResponse] -> ShowS
ListGraphqlApisResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListGraphqlApisResponse] -> ShowS
$cshowList :: [ListGraphqlApisResponse] -> ShowS
show :: ListGraphqlApisResponse -> String
$cshow :: ListGraphqlApisResponse -> String
showsPrec :: Int -> ListGraphqlApisResponse -> ShowS
$cshowsPrec :: Int -> ListGraphqlApisResponse -> ShowS
Prelude.Show, forall x. Rep ListGraphqlApisResponse x -> ListGraphqlApisResponse
forall x. ListGraphqlApisResponse -> Rep ListGraphqlApisResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListGraphqlApisResponse x -> ListGraphqlApisResponse
$cfrom :: forall x. ListGraphqlApisResponse -> Rep ListGraphqlApisResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListGraphqlApisResponse' 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:
--
-- 'graphqlApis', 'listGraphqlApisResponse_graphqlApis' - The @GraphqlApi@ objects.
--
-- 'nextToken', 'listGraphqlApisResponse_nextToken' - An identifier to pass in the next request to this operation to return
-- the next set of items in the list.
--
-- 'httpStatus', 'listGraphqlApisResponse_httpStatus' - The response's http status code.
newListGraphqlApisResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListGraphqlApisResponse
newListGraphqlApisResponse :: Int -> ListGraphqlApisResponse
newListGraphqlApisResponse Int
pHttpStatus_ =
  ListGraphqlApisResponse'
    { $sel:graphqlApis:ListGraphqlApisResponse' :: Maybe [GraphqlApi]
graphqlApis =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListGraphqlApisResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListGraphqlApisResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @GraphqlApi@ objects.
listGraphqlApisResponse_graphqlApis :: Lens.Lens' ListGraphqlApisResponse (Prelude.Maybe [GraphqlApi])
listGraphqlApisResponse_graphqlApis :: Lens' ListGraphqlApisResponse (Maybe [GraphqlApi])
listGraphqlApisResponse_graphqlApis = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGraphqlApisResponse' {Maybe [GraphqlApi]
graphqlApis :: Maybe [GraphqlApi]
$sel:graphqlApis:ListGraphqlApisResponse' :: ListGraphqlApisResponse -> Maybe [GraphqlApi]
graphqlApis} -> Maybe [GraphqlApi]
graphqlApis) (\s :: ListGraphqlApisResponse
s@ListGraphqlApisResponse' {} Maybe [GraphqlApi]
a -> ListGraphqlApisResponse
s {$sel:graphqlApis:ListGraphqlApisResponse' :: Maybe [GraphqlApi]
graphqlApis = Maybe [GraphqlApi]
a} :: ListGraphqlApisResponse) 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

-- | An identifier to pass in the next request to this operation to return
-- the next set of items in the list.
listGraphqlApisResponse_nextToken :: Lens.Lens' ListGraphqlApisResponse (Prelude.Maybe Prelude.Text)
listGraphqlApisResponse_nextToken :: Lens' ListGraphqlApisResponse (Maybe Text)
listGraphqlApisResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGraphqlApisResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListGraphqlApisResponse' :: ListGraphqlApisResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListGraphqlApisResponse
s@ListGraphqlApisResponse' {} Maybe Text
a -> ListGraphqlApisResponse
s {$sel:nextToken:ListGraphqlApisResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListGraphqlApisResponse)

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

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