{-# 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.ListTypes
-- 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 the types for a given API.
--
-- This operation returns paginated results.
module Amazonka.AppSync.ListTypes
  ( -- * Creating a Request
    ListTypes (..),
    newListTypes,

    -- * Request Lenses
    listTypes_maxResults,
    listTypes_nextToken,
    listTypes_apiId,
    listTypes_format,

    -- * Destructuring the Response
    ListTypesResponse (..),
    newListTypesResponse,

    -- * Response Lenses
    listTypesResponse_nextToken,
    listTypesResponse_types,
    listTypesResponse_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:/ 'newListTypes' smart constructor.
data ListTypes = ListTypes'
  { -- | The maximum number of results that you want the request to return.
    ListTypes -> 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.
    ListTypes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The API ID.
    ListTypes -> Text
apiId :: Prelude.Text,
    -- | The type format: SDL or JSON.
    ListTypes -> TypeDefinitionFormat
format :: TypeDefinitionFormat
  }
  deriving (ListTypes -> ListTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTypes -> ListTypes -> Bool
$c/= :: ListTypes -> ListTypes -> Bool
== :: ListTypes -> ListTypes -> Bool
$c== :: ListTypes -> ListTypes -> Bool
Prelude.Eq, ReadPrec [ListTypes]
ReadPrec ListTypes
Int -> ReadS ListTypes
ReadS [ListTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTypes]
$creadListPrec :: ReadPrec [ListTypes]
readPrec :: ReadPrec ListTypes
$creadPrec :: ReadPrec ListTypes
readList :: ReadS [ListTypes]
$creadList :: ReadS [ListTypes]
readsPrec :: Int -> ReadS ListTypes
$creadsPrec :: Int -> ReadS ListTypes
Prelude.Read, Int -> ListTypes -> ShowS
[ListTypes] -> ShowS
ListTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTypes] -> ShowS
$cshowList :: [ListTypes] -> ShowS
show :: ListTypes -> String
$cshow :: ListTypes -> String
showsPrec :: Int -> ListTypes -> ShowS
$cshowsPrec :: Int -> ListTypes -> ShowS
Prelude.Show, forall x. Rep ListTypes x -> ListTypes
forall x. ListTypes -> Rep ListTypes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTypes x -> ListTypes
$cfrom :: forall x. ListTypes -> Rep ListTypes x
Prelude.Generic)

-- |
-- Create a value of 'ListTypes' 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', 'listTypes_maxResults' - The maximum number of results that you want the request to return.
--
-- 'nextToken', 'listTypes_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.
--
-- 'apiId', 'listTypes_apiId' - The API ID.
--
-- 'format', 'listTypes_format' - The type format: SDL or JSON.
newListTypes ::
  -- | 'apiId'
  Prelude.Text ->
  -- | 'format'
  TypeDefinitionFormat ->
  ListTypes
newListTypes :: Text -> TypeDefinitionFormat -> ListTypes
newListTypes Text
pApiId_ TypeDefinitionFormat
pFormat_ =
  ListTypes'
    { $sel:maxResults:ListTypes' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListTypes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:apiId:ListTypes' :: Text
apiId = Text
pApiId_,
      $sel:format:ListTypes' :: TypeDefinitionFormat
format = TypeDefinitionFormat
pFormat_
    }

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

-- | 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.
listTypes_nextToken :: Lens.Lens' ListTypes (Prelude.Maybe Prelude.Text)
listTypes_nextToken :: Lens' ListTypes (Maybe Text)
listTypes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTypes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTypes' :: ListTypes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTypes
s@ListTypes' {} Maybe Text
a -> ListTypes
s {$sel:nextToken:ListTypes' :: Maybe Text
nextToken = Maybe Text
a} :: ListTypes)

-- | The API ID.
listTypes_apiId :: Lens.Lens' ListTypes Prelude.Text
listTypes_apiId :: Lens' ListTypes Text
listTypes_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTypes' {Text
apiId :: Text
$sel:apiId:ListTypes' :: ListTypes -> Text
apiId} -> Text
apiId) (\s :: ListTypes
s@ListTypes' {} Text
a -> ListTypes
s {$sel:apiId:ListTypes' :: Text
apiId = Text
a} :: ListTypes)

-- | The type format: SDL or JSON.
listTypes_format :: Lens.Lens' ListTypes TypeDefinitionFormat
listTypes_format :: Lens' ListTypes TypeDefinitionFormat
listTypes_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTypes' {TypeDefinitionFormat
format :: TypeDefinitionFormat
$sel:format:ListTypes' :: ListTypes -> TypeDefinitionFormat
format} -> TypeDefinitionFormat
format) (\s :: ListTypes
s@ListTypes' {} TypeDefinitionFormat
a -> ListTypes
s {$sel:format:ListTypes' :: TypeDefinitionFormat
format = TypeDefinitionFormat
a} :: ListTypes)

instance Core.AWSPager ListTypes where
  page :: ListTypes -> AWSResponse ListTypes -> Maybe ListTypes
page ListTypes
rq AWSResponse ListTypes
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListTypes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTypesResponse (Maybe Text)
listTypesResponse_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 ListTypes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTypesResponse (Maybe [Type])
listTypesResponse_types
            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.$ ListTypes
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListTypes (Maybe Text)
listTypes_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListTypes
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTypesResponse (Maybe Text)
listTypesResponse_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 ListTypes where
  type AWSResponse ListTypes = ListTypesResponse
  request :: (Service -> Service) -> ListTypes -> Request ListTypes
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 ListTypes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListTypes)))
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 [Type] -> Int -> ListTypesResponse
ListTypesResponse'
            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
"types" 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 ListTypes where
  hashWithSalt :: Int -> ListTypes -> Int
hashWithSalt Int
_salt ListTypes' {Maybe Natural
Maybe Text
Text
TypeDefinitionFormat
format :: TypeDefinitionFormat
apiId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:format:ListTypes' :: ListTypes -> TypeDefinitionFormat
$sel:apiId:ListTypes' :: ListTypes -> Text
$sel:nextToken:ListTypes' :: ListTypes -> Maybe Text
$sel:maxResults:ListTypes' :: ListTypes -> 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` Text
apiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TypeDefinitionFormat
format

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

instance Data.ToHeaders ListTypes where
  toHeaders :: ListTypes -> 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 ListTypes where
  toPath :: ListTypes -> ByteString
toPath ListTypes' {Maybe Natural
Maybe Text
Text
TypeDefinitionFormat
format :: TypeDefinitionFormat
apiId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:format:ListTypes' :: ListTypes -> TypeDefinitionFormat
$sel:apiId:ListTypes' :: ListTypes -> Text
$sel:nextToken:ListTypes' :: ListTypes -> Maybe Text
$sel:maxResults:ListTypes' :: ListTypes -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/apis/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId, ByteString
"/types"]

instance Data.ToQuery ListTypes where
  toQuery :: ListTypes -> QueryString
toQuery ListTypes' {Maybe Natural
Maybe Text
Text
TypeDefinitionFormat
format :: TypeDefinitionFormat
apiId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:format:ListTypes' :: ListTypes -> TypeDefinitionFormat
$sel:apiId:ListTypes' :: ListTypes -> Text
$sel:nextToken:ListTypes' :: ListTypes -> Maybe Text
$sel:maxResults:ListTypes' :: ListTypes -> 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,
        ByteString
"format" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: TypeDefinitionFormat
format
      ]

-- | /See:/ 'newListTypesResponse' smart constructor.
data ListTypesResponse = ListTypesResponse'
  { -- | An identifier to pass in the next request to this operation to return
    -- the next set of items in the list.
    ListTypesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The @Type@ objects.
    ListTypesResponse -> Maybe [Type]
types :: Prelude.Maybe [Type],
    -- | The response's http status code.
    ListTypesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListTypesResponse -> ListTypesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTypesResponse -> ListTypesResponse -> Bool
$c/= :: ListTypesResponse -> ListTypesResponse -> Bool
== :: ListTypesResponse -> ListTypesResponse -> Bool
$c== :: ListTypesResponse -> ListTypesResponse -> Bool
Prelude.Eq, ReadPrec [ListTypesResponse]
ReadPrec ListTypesResponse
Int -> ReadS ListTypesResponse
ReadS [ListTypesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTypesResponse]
$creadListPrec :: ReadPrec [ListTypesResponse]
readPrec :: ReadPrec ListTypesResponse
$creadPrec :: ReadPrec ListTypesResponse
readList :: ReadS [ListTypesResponse]
$creadList :: ReadS [ListTypesResponse]
readsPrec :: Int -> ReadS ListTypesResponse
$creadsPrec :: Int -> ReadS ListTypesResponse
Prelude.Read, Int -> ListTypesResponse -> ShowS
[ListTypesResponse] -> ShowS
ListTypesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTypesResponse] -> ShowS
$cshowList :: [ListTypesResponse] -> ShowS
show :: ListTypesResponse -> String
$cshow :: ListTypesResponse -> String
showsPrec :: Int -> ListTypesResponse -> ShowS
$cshowsPrec :: Int -> ListTypesResponse -> ShowS
Prelude.Show, forall x. Rep ListTypesResponse x -> ListTypesResponse
forall x. ListTypesResponse -> Rep ListTypesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTypesResponse x -> ListTypesResponse
$cfrom :: forall x. ListTypesResponse -> Rep ListTypesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTypesResponse' 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', 'listTypesResponse_nextToken' - An identifier to pass in the next request to this operation to return
-- the next set of items in the list.
--
-- 'types', 'listTypesResponse_types' - The @Type@ objects.
--
-- 'httpStatus', 'listTypesResponse_httpStatus' - The response's http status code.
newListTypesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTypesResponse
newListTypesResponse :: Int -> ListTypesResponse
newListTypesResponse Int
pHttpStatus_ =
  ListTypesResponse'
    { $sel:nextToken:ListTypesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:types:ListTypesResponse' :: Maybe [Type]
types = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTypesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The @Type@ objects.
listTypesResponse_types :: Lens.Lens' ListTypesResponse (Prelude.Maybe [Type])
listTypesResponse_types :: Lens' ListTypesResponse (Maybe [Type])
listTypesResponse_types = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTypesResponse' {Maybe [Type]
types :: Maybe [Type]
$sel:types:ListTypesResponse' :: ListTypesResponse -> Maybe [Type]
types} -> Maybe [Type]
types) (\s :: ListTypesResponse
s@ListTypesResponse' {} Maybe [Type]
a -> ListTypesResponse
s {$sel:types:ListTypesResponse' :: Maybe [Type]
types = Maybe [Type]
a} :: ListTypesResponse) 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.
listTypesResponse_httpStatus :: Lens.Lens' ListTypesResponse Prelude.Int
listTypesResponse_httpStatus :: Lens' ListTypesResponse Int
listTypesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTypesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListTypesResponse' :: ListTypesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListTypesResponse
s@ListTypesResponse' {} Int
a -> ListTypesResponse
s {$sel:httpStatus:ListTypesResponse' :: Int
httpStatus = Int
a} :: ListTypesResponse)

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