{-# 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.CloudFront.CreateFunction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a CloudFront function.
--
-- To create a function, you provide the function code and some
-- configuration information about the function. The response contains an
-- Amazon Resource Name (ARN) that uniquely identifies the function.
--
-- When you create a function, it\'s in the @DEVELOPMENT@ stage. In this
-- stage, you can test the function with @TestFunction@, and update it with
-- @UpdateFunction@.
--
-- When you\'re ready to use your function with a CloudFront distribution,
-- use @PublishFunction@ to copy the function from the @DEVELOPMENT@ stage
-- to @LIVE@. When it\'s live, you can attach the function to a
-- distribution\'s cache behavior, using the function\'s ARN.
module Amazonka.CloudFront.CreateFunction
  ( -- * Creating a Request
    CreateFunction (..),
    newCreateFunction,

    -- * Request Lenses
    createFunction_name,
    createFunction_functionConfig,
    createFunction_functionCode,

    -- * Destructuring the Response
    CreateFunctionResponse (..),
    newCreateFunctionResponse,

    -- * Response Lenses
    createFunctionResponse_eTag,
    createFunctionResponse_functionSummary,
    createFunctionResponse_location,
    createFunctionResponse_httpStatus,
  )
where

import Amazonka.CloudFront.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:/ 'newCreateFunction' smart constructor.
data CreateFunction = CreateFunction'
  { -- | A name to identify the function.
    CreateFunction -> Text
name :: Prelude.Text,
    -- | Configuration information about the function, including an optional
    -- comment and the function\'s runtime.
    CreateFunction -> FunctionConfig
functionConfig :: FunctionConfig,
    -- | The function code. For more information about writing a CloudFront
    -- function, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/writing-function-code.html Writing function code for CloudFront Functions>
    -- in the /Amazon CloudFront Developer Guide/.
    CreateFunction -> Sensitive Base64
functionCode :: Data.Sensitive Data.Base64
  }
  deriving (CreateFunction -> CreateFunction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFunction -> CreateFunction -> Bool
$c/= :: CreateFunction -> CreateFunction -> Bool
== :: CreateFunction -> CreateFunction -> Bool
$c== :: CreateFunction -> CreateFunction -> Bool
Prelude.Eq, Int -> CreateFunction -> ShowS
[CreateFunction] -> ShowS
CreateFunction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFunction] -> ShowS
$cshowList :: [CreateFunction] -> ShowS
show :: CreateFunction -> String
$cshow :: CreateFunction -> String
showsPrec :: Int -> CreateFunction -> ShowS
$cshowsPrec :: Int -> CreateFunction -> ShowS
Prelude.Show, forall x. Rep CreateFunction x -> CreateFunction
forall x. CreateFunction -> Rep CreateFunction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateFunction x -> CreateFunction
$cfrom :: forall x. CreateFunction -> Rep CreateFunction x
Prelude.Generic)

-- |
-- Create a value of 'CreateFunction' 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:
--
-- 'name', 'createFunction_name' - A name to identify the function.
--
-- 'functionConfig', 'createFunction_functionConfig' - Configuration information about the function, including an optional
-- comment and the function\'s runtime.
--
-- 'functionCode', 'createFunction_functionCode' - The function code. For more information about writing a CloudFront
-- function, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/writing-function-code.html Writing function code for CloudFront Functions>
-- in the /Amazon CloudFront Developer Guide/.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
newCreateFunction ::
  -- | 'name'
  Prelude.Text ->
  -- | 'functionConfig'
  FunctionConfig ->
  -- | 'functionCode'
  Prelude.ByteString ->
  CreateFunction
newCreateFunction :: Text -> FunctionConfig -> ByteString -> CreateFunction
newCreateFunction
  Text
pName_
  FunctionConfig
pFunctionConfig_
  ByteString
pFunctionCode_ =
    CreateFunction'
      { $sel:name:CreateFunction' :: Text
name = Text
pName_,
        $sel:functionConfig:CreateFunction' :: FunctionConfig
functionConfig = FunctionConfig
pFunctionConfig_,
        $sel:functionCode:CreateFunction' :: Sensitive Base64
functionCode =
          forall a. Iso' (Sensitive a) a
Data._Sensitive
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64
            forall t b. AReview t b -> b -> t
Lens.# ByteString
pFunctionCode_
      }

-- | A name to identify the function.
createFunction_name :: Lens.Lens' CreateFunction Prelude.Text
createFunction_name :: Lens' CreateFunction Text
createFunction_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFunction' {Text
name :: Text
$sel:name:CreateFunction' :: CreateFunction -> Text
name} -> Text
name) (\s :: CreateFunction
s@CreateFunction' {} Text
a -> CreateFunction
s {$sel:name:CreateFunction' :: Text
name = Text
a} :: CreateFunction)

-- | Configuration information about the function, including an optional
-- comment and the function\'s runtime.
createFunction_functionConfig :: Lens.Lens' CreateFunction FunctionConfig
createFunction_functionConfig :: Lens' CreateFunction FunctionConfig
createFunction_functionConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFunction' {FunctionConfig
functionConfig :: FunctionConfig
$sel:functionConfig:CreateFunction' :: CreateFunction -> FunctionConfig
functionConfig} -> FunctionConfig
functionConfig) (\s :: CreateFunction
s@CreateFunction' {} FunctionConfig
a -> CreateFunction
s {$sel:functionConfig:CreateFunction' :: FunctionConfig
functionConfig = FunctionConfig
a} :: CreateFunction)

-- | The function code. For more information about writing a CloudFront
-- function, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/writing-function-code.html Writing function code for CloudFront Functions>
-- in the /Amazon CloudFront Developer Guide/.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
createFunction_functionCode :: Lens.Lens' CreateFunction Prelude.ByteString
createFunction_functionCode :: Lens' CreateFunction ByteString
createFunction_functionCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFunction' {Sensitive Base64
functionCode :: Sensitive Base64
$sel:functionCode:CreateFunction' :: CreateFunction -> Sensitive Base64
functionCode} -> Sensitive Base64
functionCode) (\s :: CreateFunction
s@CreateFunction' {} Sensitive Base64
a -> CreateFunction
s {$sel:functionCode:CreateFunction' :: Sensitive Base64
functionCode = Sensitive Base64
a} :: CreateFunction) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64

instance Core.AWSRequest CreateFunction where
  type
    AWSResponse CreateFunction =
      CreateFunctionResponse
  request :: (Service -> Service) -> CreateFunction -> Request CreateFunction
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateFunction
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateFunction)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe FunctionSummary
-> Maybe Text
-> Int
-> CreateFunctionResponse
CreateFunctionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"ETag")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Location")
            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 CreateFunction where
  hashWithSalt :: Int -> CreateFunction -> Int
hashWithSalt Int
_salt CreateFunction' {Text
Sensitive Base64
FunctionConfig
functionCode :: Sensitive Base64
functionConfig :: FunctionConfig
name :: Text
$sel:functionCode:CreateFunction' :: CreateFunction -> Sensitive Base64
$sel:functionConfig:CreateFunction' :: CreateFunction -> FunctionConfig
$sel:name:CreateFunction' :: CreateFunction -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` FunctionConfig
functionConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Base64
functionCode

instance Prelude.NFData CreateFunction where
  rnf :: CreateFunction -> ()
rnf CreateFunction' {Text
Sensitive Base64
FunctionConfig
functionCode :: Sensitive Base64
functionConfig :: FunctionConfig
name :: Text
$sel:functionCode:CreateFunction' :: CreateFunction -> Sensitive Base64
$sel:functionConfig:CreateFunction' :: CreateFunction -> FunctionConfig
$sel:name:CreateFunction' :: CreateFunction -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf FunctionConfig
functionConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Base64
functionCode

instance Data.ToElement CreateFunction where
  toElement :: CreateFunction -> Element
toElement =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://cloudfront.amazonaws.com/doc/2020-05-31/}CreateFunctionRequest"

instance Data.ToHeaders CreateFunction where
  toHeaders :: CreateFunction -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath CreateFunction where
  toPath :: CreateFunction -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2020-05-31/function"

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

instance Data.ToXML CreateFunction where
  toXML :: CreateFunction -> XML
toXML CreateFunction' {Text
Sensitive Base64
FunctionConfig
functionCode :: Sensitive Base64
functionConfig :: FunctionConfig
name :: Text
$sel:functionCode:CreateFunction' :: CreateFunction -> Sensitive Base64
$sel:functionConfig:CreateFunction' :: CreateFunction -> FunctionConfig
$sel:name:CreateFunction' :: CreateFunction -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"Name" forall a. ToXML a => Name -> a -> XML
Data.@= Text
name,
        Name
"FunctionConfig" forall a. ToXML a => Name -> a -> XML
Data.@= FunctionConfig
functionConfig,
        Name
"FunctionCode" forall a. ToXML a => Name -> a -> XML
Data.@= Sensitive Base64
functionCode
      ]

-- | /See:/ 'newCreateFunctionResponse' smart constructor.
data CreateFunctionResponse = CreateFunctionResponse'
  { -- | The version identifier for the current version of the CloudFront
    -- function.
    CreateFunctionResponse -> Maybe Text
eTag :: Prelude.Maybe Prelude.Text,
    -- | Contains configuration information and metadata about a CloudFront
    -- function.
    CreateFunctionResponse -> Maybe FunctionSummary
functionSummary :: Prelude.Maybe FunctionSummary,
    -- | The URL of the CloudFront function. Use the URL to manage the function
    -- with the CloudFront API.
    CreateFunctionResponse -> Maybe Text
location :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateFunctionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateFunctionResponse -> CreateFunctionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFunctionResponse -> CreateFunctionResponse -> Bool
$c/= :: CreateFunctionResponse -> CreateFunctionResponse -> Bool
== :: CreateFunctionResponse -> CreateFunctionResponse -> Bool
$c== :: CreateFunctionResponse -> CreateFunctionResponse -> Bool
Prelude.Eq, ReadPrec [CreateFunctionResponse]
ReadPrec CreateFunctionResponse
Int -> ReadS CreateFunctionResponse
ReadS [CreateFunctionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFunctionResponse]
$creadListPrec :: ReadPrec [CreateFunctionResponse]
readPrec :: ReadPrec CreateFunctionResponse
$creadPrec :: ReadPrec CreateFunctionResponse
readList :: ReadS [CreateFunctionResponse]
$creadList :: ReadS [CreateFunctionResponse]
readsPrec :: Int -> ReadS CreateFunctionResponse
$creadsPrec :: Int -> ReadS CreateFunctionResponse
Prelude.Read, Int -> CreateFunctionResponse -> ShowS
[CreateFunctionResponse] -> ShowS
CreateFunctionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFunctionResponse] -> ShowS
$cshowList :: [CreateFunctionResponse] -> ShowS
show :: CreateFunctionResponse -> String
$cshow :: CreateFunctionResponse -> String
showsPrec :: Int -> CreateFunctionResponse -> ShowS
$cshowsPrec :: Int -> CreateFunctionResponse -> ShowS
Prelude.Show, forall x. Rep CreateFunctionResponse x -> CreateFunctionResponse
forall x. CreateFunctionResponse -> Rep CreateFunctionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateFunctionResponse x -> CreateFunctionResponse
$cfrom :: forall x. CreateFunctionResponse -> Rep CreateFunctionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateFunctionResponse' 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:
--
-- 'eTag', 'createFunctionResponse_eTag' - The version identifier for the current version of the CloudFront
-- function.
--
-- 'functionSummary', 'createFunctionResponse_functionSummary' - Contains configuration information and metadata about a CloudFront
-- function.
--
-- 'location', 'createFunctionResponse_location' - The URL of the CloudFront function. Use the URL to manage the function
-- with the CloudFront API.
--
-- 'httpStatus', 'createFunctionResponse_httpStatus' - The response's http status code.
newCreateFunctionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateFunctionResponse
newCreateFunctionResponse :: Int -> CreateFunctionResponse
newCreateFunctionResponse Int
pHttpStatus_ =
  CreateFunctionResponse'
    { $sel:eTag:CreateFunctionResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
      $sel:functionSummary:CreateFunctionResponse' :: Maybe FunctionSummary
functionSummary = forall a. Maybe a
Prelude.Nothing,
      $sel:location:CreateFunctionResponse' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateFunctionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The version identifier for the current version of the CloudFront
-- function.
createFunctionResponse_eTag :: Lens.Lens' CreateFunctionResponse (Prelude.Maybe Prelude.Text)
createFunctionResponse_eTag :: Lens' CreateFunctionResponse (Maybe Text)
createFunctionResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFunctionResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:CreateFunctionResponse' :: CreateFunctionResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: CreateFunctionResponse
s@CreateFunctionResponse' {} Maybe Text
a -> CreateFunctionResponse
s {$sel:eTag:CreateFunctionResponse' :: Maybe Text
eTag = Maybe Text
a} :: CreateFunctionResponse)

-- | Contains configuration information and metadata about a CloudFront
-- function.
createFunctionResponse_functionSummary :: Lens.Lens' CreateFunctionResponse (Prelude.Maybe FunctionSummary)
createFunctionResponse_functionSummary :: Lens' CreateFunctionResponse (Maybe FunctionSummary)
createFunctionResponse_functionSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFunctionResponse' {Maybe FunctionSummary
functionSummary :: Maybe FunctionSummary
$sel:functionSummary:CreateFunctionResponse' :: CreateFunctionResponse -> Maybe FunctionSummary
functionSummary} -> Maybe FunctionSummary
functionSummary) (\s :: CreateFunctionResponse
s@CreateFunctionResponse' {} Maybe FunctionSummary
a -> CreateFunctionResponse
s {$sel:functionSummary:CreateFunctionResponse' :: Maybe FunctionSummary
functionSummary = Maybe FunctionSummary
a} :: CreateFunctionResponse)

-- | The URL of the CloudFront function. Use the URL to manage the function
-- with the CloudFront API.
createFunctionResponse_location :: Lens.Lens' CreateFunctionResponse (Prelude.Maybe Prelude.Text)
createFunctionResponse_location :: Lens' CreateFunctionResponse (Maybe Text)
createFunctionResponse_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFunctionResponse' {Maybe Text
location :: Maybe Text
$sel:location:CreateFunctionResponse' :: CreateFunctionResponse -> Maybe Text
location} -> Maybe Text
location) (\s :: CreateFunctionResponse
s@CreateFunctionResponse' {} Maybe Text
a -> CreateFunctionResponse
s {$sel:location:CreateFunctionResponse' :: Maybe Text
location = Maybe Text
a} :: CreateFunctionResponse)

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

instance Prelude.NFData CreateFunctionResponse where
  rnf :: CreateFunctionResponse -> ()
rnf CreateFunctionResponse' {Int
Maybe Text
Maybe FunctionSummary
httpStatus :: Int
location :: Maybe Text
functionSummary :: Maybe FunctionSummary
eTag :: Maybe Text
$sel:httpStatus:CreateFunctionResponse' :: CreateFunctionResponse -> Int
$sel:location:CreateFunctionResponse' :: CreateFunctionResponse -> Maybe Text
$sel:functionSummary:CreateFunctionResponse' :: CreateFunctionResponse -> Maybe FunctionSummary
$sel:eTag:CreateFunctionResponse' :: CreateFunctionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eTag
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FunctionSummary
functionSummary
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus