{-# 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.Glue.ListSchemas
-- 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 schemas with minimal details. Schemas in Deleting
-- status will not be included in the results. Empty results will be
-- returned if there are no schemas available.
--
-- When the @RegistryId@ is not provided, all the schemas across registries
-- will be part of the API response.
--
-- This operation returns paginated results.
module Amazonka.Glue.ListSchemas
  ( -- * Creating a Request
    ListSchemas (..),
    newListSchemas,

    -- * Request Lenses
    listSchemas_maxResults,
    listSchemas_nextToken,
    listSchemas_registryId,

    -- * Destructuring the Response
    ListSchemasResponse (..),
    newListSchemasResponse,

    -- * Response Lenses
    listSchemasResponse_nextToken,
    listSchemasResponse_schemas,
    listSchemasResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListSchemas' smart constructor.
data ListSchemas = ListSchemas'
  { -- | Maximum number of results required per page. If the value is not
    -- supplied, this will be defaulted to 25 per page.
    ListSchemas -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A continuation token, if this is a continuation call.
    ListSchemas -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A wrapper structure that may contain the registry name and Amazon
    -- Resource Name (ARN).
    ListSchemas -> Maybe RegistryId
registryId :: Prelude.Maybe RegistryId
  }
  deriving (ListSchemas -> ListSchemas -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSchemas -> ListSchemas -> Bool
$c/= :: ListSchemas -> ListSchemas -> Bool
== :: ListSchemas -> ListSchemas -> Bool
$c== :: ListSchemas -> ListSchemas -> Bool
Prelude.Eq, ReadPrec [ListSchemas]
ReadPrec ListSchemas
Int -> ReadS ListSchemas
ReadS [ListSchemas]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSchemas]
$creadListPrec :: ReadPrec [ListSchemas]
readPrec :: ReadPrec ListSchemas
$creadPrec :: ReadPrec ListSchemas
readList :: ReadS [ListSchemas]
$creadList :: ReadS [ListSchemas]
readsPrec :: Int -> ReadS ListSchemas
$creadsPrec :: Int -> ReadS ListSchemas
Prelude.Read, Int -> ListSchemas -> ShowS
[ListSchemas] -> ShowS
ListSchemas -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSchemas] -> ShowS
$cshowList :: [ListSchemas] -> ShowS
show :: ListSchemas -> String
$cshow :: ListSchemas -> String
showsPrec :: Int -> ListSchemas -> ShowS
$cshowsPrec :: Int -> ListSchemas -> ShowS
Prelude.Show, forall x. Rep ListSchemas x -> ListSchemas
forall x. ListSchemas -> Rep ListSchemas x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSchemas x -> ListSchemas
$cfrom :: forall x. ListSchemas -> Rep ListSchemas x
Prelude.Generic)

-- |
-- Create a value of 'ListSchemas' 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', 'listSchemas_maxResults' - Maximum number of results required per page. If the value is not
-- supplied, this will be defaulted to 25 per page.
--
-- 'nextToken', 'listSchemas_nextToken' - A continuation token, if this is a continuation call.
--
-- 'registryId', 'listSchemas_registryId' - A wrapper structure that may contain the registry name and Amazon
-- Resource Name (ARN).
newListSchemas ::
  ListSchemas
newListSchemas :: ListSchemas
newListSchemas =
  ListSchemas'
    { $sel:maxResults:ListSchemas' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListSchemas' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:ListSchemas' :: Maybe RegistryId
registryId = forall a. Maybe a
Prelude.Nothing
    }

-- | Maximum number of results required per page. If the value is not
-- supplied, this will be defaulted to 25 per page.
listSchemas_maxResults :: Lens.Lens' ListSchemas (Prelude.Maybe Prelude.Natural)
listSchemas_maxResults :: Lens' ListSchemas (Maybe Natural)
listSchemas_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSchemas' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListSchemas' :: ListSchemas -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListSchemas
s@ListSchemas' {} Maybe Natural
a -> ListSchemas
s {$sel:maxResults:ListSchemas' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListSchemas)

-- | A continuation token, if this is a continuation call.
listSchemas_nextToken :: Lens.Lens' ListSchemas (Prelude.Maybe Prelude.Text)
listSchemas_nextToken :: Lens' ListSchemas (Maybe Text)
listSchemas_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSchemas' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSchemas' :: ListSchemas -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSchemas
s@ListSchemas' {} Maybe Text
a -> ListSchemas
s {$sel:nextToken:ListSchemas' :: Maybe Text
nextToken = Maybe Text
a} :: ListSchemas)

-- | A wrapper structure that may contain the registry name and Amazon
-- Resource Name (ARN).
listSchemas_registryId :: Lens.Lens' ListSchemas (Prelude.Maybe RegistryId)
listSchemas_registryId :: Lens' ListSchemas (Maybe RegistryId)
listSchemas_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSchemas' {Maybe RegistryId
registryId :: Maybe RegistryId
$sel:registryId:ListSchemas' :: ListSchemas -> Maybe RegistryId
registryId} -> Maybe RegistryId
registryId) (\s :: ListSchemas
s@ListSchemas' {} Maybe RegistryId
a -> ListSchemas
s {$sel:registryId:ListSchemas' :: Maybe RegistryId
registryId = Maybe RegistryId
a} :: ListSchemas)

instance Core.AWSPager ListSchemas where
  page :: ListSchemas -> AWSResponse ListSchemas -> Maybe ListSchemas
page ListSchemas
rq AWSResponse ListSchemas
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListSchemas
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSchemasResponse (Maybe Text)
listSchemasResponse_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 ListSchemas
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSchemasResponse (Maybe [SchemaListItem])
listSchemasResponse_schemas
            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.$ ListSchemas
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListSchemas (Maybe Text)
listSchemas_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListSchemas
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSchemasResponse (Maybe Text)
listSchemasResponse_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 ListSchemas where
  type AWSResponse ListSchemas = ListSchemasResponse
  request :: (Service -> Service) -> ListSchemas -> Request ListSchemas
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 ListSchemas
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListSchemas)))
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 [SchemaListItem] -> Int -> ListSchemasResponse
ListSchemasResponse'
            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
"Schemas" 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 ListSchemas where
  hashWithSalt :: Int -> ListSchemas -> Int
hashWithSalt Int
_salt ListSchemas' {Maybe Natural
Maybe Text
Maybe RegistryId
registryId :: Maybe RegistryId
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:registryId:ListSchemas' :: ListSchemas -> Maybe RegistryId
$sel:nextToken:ListSchemas' :: ListSchemas -> Maybe Text
$sel:maxResults:ListSchemas' :: ListSchemas -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RegistryId
registryId

instance Prelude.NFData ListSchemas where
  rnf :: ListSchemas -> ()
rnf ListSchemas' {Maybe Natural
Maybe Text
Maybe RegistryId
registryId :: Maybe RegistryId
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:registryId:ListSchemas' :: ListSchemas -> Maybe RegistryId
$sel:nextToken:ListSchemas' :: ListSchemas -> Maybe Text
$sel:maxResults:ListSchemas' :: ListSchemas -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RegistryId
registryId

instance Data.ToHeaders ListSchemas where
  toHeaders :: ListSchemas -> 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
"AWSGlue.ListSchemas" :: 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 ListSchemas where
  toJSON :: ListSchemas -> Value
toJSON ListSchemas' {Maybe Natural
Maybe Text
Maybe RegistryId
registryId :: Maybe RegistryId
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:registryId:ListSchemas' :: ListSchemas -> Maybe RegistryId
$sel:nextToken:ListSchemas' :: ListSchemas -> Maybe Text
$sel:maxResults:ListSchemas' :: ListSchemas -> 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,
            (Key
"RegistryId" 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 RegistryId
registryId
          ]
      )

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

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

-- | /See:/ 'newListSchemasResponse' smart constructor.
data ListSchemasResponse = ListSchemasResponse'
  { -- | A continuation token for paginating the returned list of tokens,
    -- returned if the current segment of the list is not the last.
    ListSchemasResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of @SchemaListItem@ objects containing details of each schema.
    ListSchemasResponse -> Maybe [SchemaListItem]
schemas :: Prelude.Maybe [SchemaListItem],
    -- | The response's http status code.
    ListSchemasResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListSchemasResponse -> ListSchemasResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSchemasResponse -> ListSchemasResponse -> Bool
$c/= :: ListSchemasResponse -> ListSchemasResponse -> Bool
== :: ListSchemasResponse -> ListSchemasResponse -> Bool
$c== :: ListSchemasResponse -> ListSchemasResponse -> Bool
Prelude.Eq, ReadPrec [ListSchemasResponse]
ReadPrec ListSchemasResponse
Int -> ReadS ListSchemasResponse
ReadS [ListSchemasResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSchemasResponse]
$creadListPrec :: ReadPrec [ListSchemasResponse]
readPrec :: ReadPrec ListSchemasResponse
$creadPrec :: ReadPrec ListSchemasResponse
readList :: ReadS [ListSchemasResponse]
$creadList :: ReadS [ListSchemasResponse]
readsPrec :: Int -> ReadS ListSchemasResponse
$creadsPrec :: Int -> ReadS ListSchemasResponse
Prelude.Read, Int -> ListSchemasResponse -> ShowS
[ListSchemasResponse] -> ShowS
ListSchemasResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSchemasResponse] -> ShowS
$cshowList :: [ListSchemasResponse] -> ShowS
show :: ListSchemasResponse -> String
$cshow :: ListSchemasResponse -> String
showsPrec :: Int -> ListSchemasResponse -> ShowS
$cshowsPrec :: Int -> ListSchemasResponse -> ShowS
Prelude.Show, forall x. Rep ListSchemasResponse x -> ListSchemasResponse
forall x. ListSchemasResponse -> Rep ListSchemasResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSchemasResponse x -> ListSchemasResponse
$cfrom :: forall x. ListSchemasResponse -> Rep ListSchemasResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListSchemasResponse' 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', 'listSchemasResponse_nextToken' - A continuation token for paginating the returned list of tokens,
-- returned if the current segment of the list is not the last.
--
-- 'schemas', 'listSchemasResponse_schemas' - An array of @SchemaListItem@ objects containing details of each schema.
--
-- 'httpStatus', 'listSchemasResponse_httpStatus' - The response's http status code.
newListSchemasResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListSchemasResponse
newListSchemasResponse :: Int -> ListSchemasResponse
newListSchemasResponse Int
pHttpStatus_ =
  ListSchemasResponse'
    { $sel:nextToken:ListSchemasResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:schemas:ListSchemasResponse' :: Maybe [SchemaListItem]
schemas = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListSchemasResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A continuation token for paginating the returned list of tokens,
-- returned if the current segment of the list is not the last.
listSchemasResponse_nextToken :: Lens.Lens' ListSchemasResponse (Prelude.Maybe Prelude.Text)
listSchemasResponse_nextToken :: Lens' ListSchemasResponse (Maybe Text)
listSchemasResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSchemasResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSchemasResponse' :: ListSchemasResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSchemasResponse
s@ListSchemasResponse' {} Maybe Text
a -> ListSchemasResponse
s {$sel:nextToken:ListSchemasResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListSchemasResponse)

-- | An array of @SchemaListItem@ objects containing details of each schema.
listSchemasResponse_schemas :: Lens.Lens' ListSchemasResponse (Prelude.Maybe [SchemaListItem])
listSchemasResponse_schemas :: Lens' ListSchemasResponse (Maybe [SchemaListItem])
listSchemasResponse_schemas = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSchemasResponse' {Maybe [SchemaListItem]
schemas :: Maybe [SchemaListItem]
$sel:schemas:ListSchemasResponse' :: ListSchemasResponse -> Maybe [SchemaListItem]
schemas} -> Maybe [SchemaListItem]
schemas) (\s :: ListSchemasResponse
s@ListSchemasResponse' {} Maybe [SchemaListItem]
a -> ListSchemasResponse
s {$sel:schemas:ListSchemasResponse' :: Maybe [SchemaListItem]
schemas = Maybe [SchemaListItem]
a} :: ListSchemasResponse) 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.
listSchemasResponse_httpStatus :: Lens.Lens' ListSchemasResponse Prelude.Int
listSchemasResponse_httpStatus :: Lens' ListSchemasResponse Int
listSchemasResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSchemasResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListSchemasResponse' :: ListSchemasResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListSchemasResponse
s@ListSchemasResponse' {} Int
a -> ListSchemasResponse
s {$sel:httpStatus:ListSchemasResponse' :: Int
httpStatus = Int
a} :: ListSchemasResponse)

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