{-# 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.Kafka.UpdateBrokerCount
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the number of broker nodes in the cluster.
module Amazonka.Kafka.UpdateBrokerCount
  ( -- * Creating a Request
    UpdateBrokerCount (..),
    newUpdateBrokerCount,

    -- * Request Lenses
    updateBrokerCount_clusterArn,
    updateBrokerCount_currentVersion,
    updateBrokerCount_targetNumberOfBrokerNodes,

    -- * Destructuring the Response
    UpdateBrokerCountResponse (..),
    newUpdateBrokerCountResponse,

    -- * Response Lenses
    updateBrokerCountResponse_clusterArn,
    updateBrokerCountResponse_clusterOperationArn,
    updateBrokerCountResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateBrokerCount' smart constructor.
data UpdateBrokerCount = UpdateBrokerCount'
  { -- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
    UpdateBrokerCount -> Text
clusterArn :: Prelude.Text,
    -- | The version of cluster to update from. A successful operation will then
    -- generate a new version.
    UpdateBrokerCount -> Text
currentVersion :: Prelude.Text,
    -- | The number of broker nodes that you want the cluster to have after this
    -- operation completes successfully.
    UpdateBrokerCount -> Natural
targetNumberOfBrokerNodes :: Prelude.Natural
  }
  deriving (UpdateBrokerCount -> UpdateBrokerCount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateBrokerCount -> UpdateBrokerCount -> Bool
$c/= :: UpdateBrokerCount -> UpdateBrokerCount -> Bool
== :: UpdateBrokerCount -> UpdateBrokerCount -> Bool
$c== :: UpdateBrokerCount -> UpdateBrokerCount -> Bool
Prelude.Eq, ReadPrec [UpdateBrokerCount]
ReadPrec UpdateBrokerCount
Int -> ReadS UpdateBrokerCount
ReadS [UpdateBrokerCount]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateBrokerCount]
$creadListPrec :: ReadPrec [UpdateBrokerCount]
readPrec :: ReadPrec UpdateBrokerCount
$creadPrec :: ReadPrec UpdateBrokerCount
readList :: ReadS [UpdateBrokerCount]
$creadList :: ReadS [UpdateBrokerCount]
readsPrec :: Int -> ReadS UpdateBrokerCount
$creadsPrec :: Int -> ReadS UpdateBrokerCount
Prelude.Read, Int -> UpdateBrokerCount -> ShowS
[UpdateBrokerCount] -> ShowS
UpdateBrokerCount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateBrokerCount] -> ShowS
$cshowList :: [UpdateBrokerCount] -> ShowS
show :: UpdateBrokerCount -> String
$cshow :: UpdateBrokerCount -> String
showsPrec :: Int -> UpdateBrokerCount -> ShowS
$cshowsPrec :: Int -> UpdateBrokerCount -> ShowS
Prelude.Show, forall x. Rep UpdateBrokerCount x -> UpdateBrokerCount
forall x. UpdateBrokerCount -> Rep UpdateBrokerCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateBrokerCount x -> UpdateBrokerCount
$cfrom :: forall x. UpdateBrokerCount -> Rep UpdateBrokerCount x
Prelude.Generic)

-- |
-- Create a value of 'UpdateBrokerCount' 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:
--
-- 'clusterArn', 'updateBrokerCount_clusterArn' - The Amazon Resource Name (ARN) that uniquely identifies the cluster.
--
-- 'currentVersion', 'updateBrokerCount_currentVersion' - The version of cluster to update from. A successful operation will then
-- generate a new version.
--
-- 'targetNumberOfBrokerNodes', 'updateBrokerCount_targetNumberOfBrokerNodes' - The number of broker nodes that you want the cluster to have after this
-- operation completes successfully.
newUpdateBrokerCount ::
  -- | 'clusterArn'
  Prelude.Text ->
  -- | 'currentVersion'
  Prelude.Text ->
  -- | 'targetNumberOfBrokerNodes'
  Prelude.Natural ->
  UpdateBrokerCount
newUpdateBrokerCount :: Text -> Text -> Natural -> UpdateBrokerCount
newUpdateBrokerCount
  Text
pClusterArn_
  Text
pCurrentVersion_
  Natural
pTargetNumberOfBrokerNodes_ =
    UpdateBrokerCount'
      { $sel:clusterArn:UpdateBrokerCount' :: Text
clusterArn = Text
pClusterArn_,
        $sel:currentVersion:UpdateBrokerCount' :: Text
currentVersion = Text
pCurrentVersion_,
        $sel:targetNumberOfBrokerNodes:UpdateBrokerCount' :: Natural
targetNumberOfBrokerNodes =
          Natural
pTargetNumberOfBrokerNodes_
      }

-- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
updateBrokerCount_clusterArn :: Lens.Lens' UpdateBrokerCount Prelude.Text
updateBrokerCount_clusterArn :: Lens' UpdateBrokerCount Text
updateBrokerCount_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBrokerCount' {Text
clusterArn :: Text
$sel:clusterArn:UpdateBrokerCount' :: UpdateBrokerCount -> Text
clusterArn} -> Text
clusterArn) (\s :: UpdateBrokerCount
s@UpdateBrokerCount' {} Text
a -> UpdateBrokerCount
s {$sel:clusterArn:UpdateBrokerCount' :: Text
clusterArn = Text
a} :: UpdateBrokerCount)

-- | The version of cluster to update from. A successful operation will then
-- generate a new version.
updateBrokerCount_currentVersion :: Lens.Lens' UpdateBrokerCount Prelude.Text
updateBrokerCount_currentVersion :: Lens' UpdateBrokerCount Text
updateBrokerCount_currentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBrokerCount' {Text
currentVersion :: Text
$sel:currentVersion:UpdateBrokerCount' :: UpdateBrokerCount -> Text
currentVersion} -> Text
currentVersion) (\s :: UpdateBrokerCount
s@UpdateBrokerCount' {} Text
a -> UpdateBrokerCount
s {$sel:currentVersion:UpdateBrokerCount' :: Text
currentVersion = Text
a} :: UpdateBrokerCount)

-- | The number of broker nodes that you want the cluster to have after this
-- operation completes successfully.
updateBrokerCount_targetNumberOfBrokerNodes :: Lens.Lens' UpdateBrokerCount Prelude.Natural
updateBrokerCount_targetNumberOfBrokerNodes :: Lens' UpdateBrokerCount Natural
updateBrokerCount_targetNumberOfBrokerNodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBrokerCount' {Natural
targetNumberOfBrokerNodes :: Natural
$sel:targetNumberOfBrokerNodes:UpdateBrokerCount' :: UpdateBrokerCount -> Natural
targetNumberOfBrokerNodes} -> Natural
targetNumberOfBrokerNodes) (\s :: UpdateBrokerCount
s@UpdateBrokerCount' {} Natural
a -> UpdateBrokerCount
s {$sel:targetNumberOfBrokerNodes:UpdateBrokerCount' :: Natural
targetNumberOfBrokerNodes = Natural
a} :: UpdateBrokerCount)

instance Core.AWSRequest UpdateBrokerCount where
  type
    AWSResponse UpdateBrokerCount =
      UpdateBrokerCountResponse
  request :: (Service -> Service)
-> UpdateBrokerCount -> Request UpdateBrokerCount
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateBrokerCount
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateBrokerCount)))
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 Text -> Int -> UpdateBrokerCountResponse
UpdateBrokerCountResponse'
            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
"clusterArn")
            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
"clusterOperationArn")
            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 UpdateBrokerCount where
  hashWithSalt :: Int -> UpdateBrokerCount -> Int
hashWithSalt Int
_salt UpdateBrokerCount' {Natural
Text
targetNumberOfBrokerNodes :: Natural
currentVersion :: Text
clusterArn :: Text
$sel:targetNumberOfBrokerNodes:UpdateBrokerCount' :: UpdateBrokerCount -> Natural
$sel:currentVersion:UpdateBrokerCount' :: UpdateBrokerCount -> Text
$sel:clusterArn:UpdateBrokerCount' :: UpdateBrokerCount -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
currentVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
targetNumberOfBrokerNodes

instance Prelude.NFData UpdateBrokerCount where
  rnf :: UpdateBrokerCount -> ()
rnf UpdateBrokerCount' {Natural
Text
targetNumberOfBrokerNodes :: Natural
currentVersion :: Text
clusterArn :: Text
$sel:targetNumberOfBrokerNodes:UpdateBrokerCount' :: UpdateBrokerCount -> Natural
$sel:currentVersion:UpdateBrokerCount' :: UpdateBrokerCount -> Text
$sel:clusterArn:UpdateBrokerCount' :: UpdateBrokerCount -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
currentVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
targetNumberOfBrokerNodes

instance Data.ToHeaders UpdateBrokerCount where
  toHeaders :: UpdateBrokerCount -> 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.ToJSON UpdateBrokerCount where
  toJSON :: UpdateBrokerCount -> Value
toJSON UpdateBrokerCount' {Natural
Text
targetNumberOfBrokerNodes :: Natural
currentVersion :: Text
clusterArn :: Text
$sel:targetNumberOfBrokerNodes:UpdateBrokerCount' :: UpdateBrokerCount -> Natural
$sel:currentVersion:UpdateBrokerCount' :: UpdateBrokerCount -> Text
$sel:clusterArn:UpdateBrokerCount' :: UpdateBrokerCount -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"currentVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
currentVersion),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"targetNumberOfBrokerNodes"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
targetNumberOfBrokerNodes
              )
          ]
      )

instance Data.ToPath UpdateBrokerCount where
  toPath :: UpdateBrokerCount -> ByteString
toPath UpdateBrokerCount' {Natural
Text
targetNumberOfBrokerNodes :: Natural
currentVersion :: Text
clusterArn :: Text
$sel:targetNumberOfBrokerNodes:UpdateBrokerCount' :: UpdateBrokerCount -> Natural
$sel:currentVersion:UpdateBrokerCount' :: UpdateBrokerCount -> Text
$sel:clusterArn:UpdateBrokerCount' :: UpdateBrokerCount -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/clusters/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn,
        ByteString
"/nodes/count"
      ]

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

-- | /See:/ 'newUpdateBrokerCountResponse' smart constructor.
data UpdateBrokerCountResponse = UpdateBrokerCountResponse'
  { -- | The Amazon Resource Name (ARN) of the cluster.
    UpdateBrokerCountResponse -> Maybe Text
clusterArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the cluster operation.
    UpdateBrokerCountResponse -> Maybe Text
clusterOperationArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateBrokerCountResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateBrokerCountResponse -> UpdateBrokerCountResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateBrokerCountResponse -> UpdateBrokerCountResponse -> Bool
$c/= :: UpdateBrokerCountResponse -> UpdateBrokerCountResponse -> Bool
== :: UpdateBrokerCountResponse -> UpdateBrokerCountResponse -> Bool
$c== :: UpdateBrokerCountResponse -> UpdateBrokerCountResponse -> Bool
Prelude.Eq, ReadPrec [UpdateBrokerCountResponse]
ReadPrec UpdateBrokerCountResponse
Int -> ReadS UpdateBrokerCountResponse
ReadS [UpdateBrokerCountResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateBrokerCountResponse]
$creadListPrec :: ReadPrec [UpdateBrokerCountResponse]
readPrec :: ReadPrec UpdateBrokerCountResponse
$creadPrec :: ReadPrec UpdateBrokerCountResponse
readList :: ReadS [UpdateBrokerCountResponse]
$creadList :: ReadS [UpdateBrokerCountResponse]
readsPrec :: Int -> ReadS UpdateBrokerCountResponse
$creadsPrec :: Int -> ReadS UpdateBrokerCountResponse
Prelude.Read, Int -> UpdateBrokerCountResponse -> ShowS
[UpdateBrokerCountResponse] -> ShowS
UpdateBrokerCountResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateBrokerCountResponse] -> ShowS
$cshowList :: [UpdateBrokerCountResponse] -> ShowS
show :: UpdateBrokerCountResponse -> String
$cshow :: UpdateBrokerCountResponse -> String
showsPrec :: Int -> UpdateBrokerCountResponse -> ShowS
$cshowsPrec :: Int -> UpdateBrokerCountResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateBrokerCountResponse x -> UpdateBrokerCountResponse
forall x.
UpdateBrokerCountResponse -> Rep UpdateBrokerCountResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateBrokerCountResponse x -> UpdateBrokerCountResponse
$cfrom :: forall x.
UpdateBrokerCountResponse -> Rep UpdateBrokerCountResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateBrokerCountResponse' 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:
--
-- 'clusterArn', 'updateBrokerCountResponse_clusterArn' - The Amazon Resource Name (ARN) of the cluster.
--
-- 'clusterOperationArn', 'updateBrokerCountResponse_clusterOperationArn' - The Amazon Resource Name (ARN) of the cluster operation.
--
-- 'httpStatus', 'updateBrokerCountResponse_httpStatus' - The response's http status code.
newUpdateBrokerCountResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateBrokerCountResponse
newUpdateBrokerCountResponse :: Int -> UpdateBrokerCountResponse
newUpdateBrokerCountResponse Int
pHttpStatus_ =
  UpdateBrokerCountResponse'
    { $sel:clusterArn:UpdateBrokerCountResponse' :: Maybe Text
clusterArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clusterOperationArn:UpdateBrokerCountResponse' :: Maybe Text
clusterOperationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateBrokerCountResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the cluster.
updateBrokerCountResponse_clusterArn :: Lens.Lens' UpdateBrokerCountResponse (Prelude.Maybe Prelude.Text)
updateBrokerCountResponse_clusterArn :: Lens' UpdateBrokerCountResponse (Maybe Text)
updateBrokerCountResponse_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBrokerCountResponse' {Maybe Text
clusterArn :: Maybe Text
$sel:clusterArn:UpdateBrokerCountResponse' :: UpdateBrokerCountResponse -> Maybe Text
clusterArn} -> Maybe Text
clusterArn) (\s :: UpdateBrokerCountResponse
s@UpdateBrokerCountResponse' {} Maybe Text
a -> UpdateBrokerCountResponse
s {$sel:clusterArn:UpdateBrokerCountResponse' :: Maybe Text
clusterArn = Maybe Text
a} :: UpdateBrokerCountResponse)

-- | The Amazon Resource Name (ARN) of the cluster operation.
updateBrokerCountResponse_clusterOperationArn :: Lens.Lens' UpdateBrokerCountResponse (Prelude.Maybe Prelude.Text)
updateBrokerCountResponse_clusterOperationArn :: Lens' UpdateBrokerCountResponse (Maybe Text)
updateBrokerCountResponse_clusterOperationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBrokerCountResponse' {Maybe Text
clusterOperationArn :: Maybe Text
$sel:clusterOperationArn:UpdateBrokerCountResponse' :: UpdateBrokerCountResponse -> Maybe Text
clusterOperationArn} -> Maybe Text
clusterOperationArn) (\s :: UpdateBrokerCountResponse
s@UpdateBrokerCountResponse' {} Maybe Text
a -> UpdateBrokerCountResponse
s {$sel:clusterOperationArn:UpdateBrokerCountResponse' :: Maybe Text
clusterOperationArn = Maybe Text
a} :: UpdateBrokerCountResponse)

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

instance Prelude.NFData UpdateBrokerCountResponse where
  rnf :: UpdateBrokerCountResponse -> ()
rnf UpdateBrokerCountResponse' {Int
Maybe Text
httpStatus :: Int
clusterOperationArn :: Maybe Text
clusterArn :: Maybe Text
$sel:httpStatus:UpdateBrokerCountResponse' :: UpdateBrokerCountResponse -> Int
$sel:clusterOperationArn:UpdateBrokerCountResponse' :: UpdateBrokerCountResponse -> Maybe Text
$sel:clusterArn:UpdateBrokerCountResponse' :: UpdateBrokerCountResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterOperationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus