{-# 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.AmplifyBackend.RemoveAllBackends
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes all backend environments from your Amplify project.
module Amazonka.AmplifyBackend.RemoveAllBackends
  ( -- * Creating a Request
    RemoveAllBackends (..),
    newRemoveAllBackends,

    -- * Request Lenses
    removeAllBackends_cleanAmplifyApp,
    removeAllBackends_appId,

    -- * Destructuring the Response
    RemoveAllBackendsResponse (..),
    newRemoveAllBackendsResponse,

    -- * Response Lenses
    removeAllBackendsResponse_appId,
    removeAllBackendsResponse_error,
    removeAllBackendsResponse_jobId,
    removeAllBackendsResponse_operation,
    removeAllBackendsResponse_status,
    removeAllBackendsResponse_httpStatus,
  )
where

import Amazonka.AmplifyBackend.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

-- | The request body for RemoveAllBackends.
--
-- /See:/ 'newRemoveAllBackends' smart constructor.
data RemoveAllBackends = RemoveAllBackends'
  { -- | Cleans up the Amplify Console app if this value is set to true.
    RemoveAllBackends -> Maybe Bool
cleanAmplifyApp :: Prelude.Maybe Prelude.Bool,
    -- | The app ID.
    RemoveAllBackends -> Text
appId :: Prelude.Text
  }
  deriving (RemoveAllBackends -> RemoveAllBackends -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveAllBackends -> RemoveAllBackends -> Bool
$c/= :: RemoveAllBackends -> RemoveAllBackends -> Bool
== :: RemoveAllBackends -> RemoveAllBackends -> Bool
$c== :: RemoveAllBackends -> RemoveAllBackends -> Bool
Prelude.Eq, ReadPrec [RemoveAllBackends]
ReadPrec RemoveAllBackends
Int -> ReadS RemoveAllBackends
ReadS [RemoveAllBackends]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveAllBackends]
$creadListPrec :: ReadPrec [RemoveAllBackends]
readPrec :: ReadPrec RemoveAllBackends
$creadPrec :: ReadPrec RemoveAllBackends
readList :: ReadS [RemoveAllBackends]
$creadList :: ReadS [RemoveAllBackends]
readsPrec :: Int -> ReadS RemoveAllBackends
$creadsPrec :: Int -> ReadS RemoveAllBackends
Prelude.Read, Int -> RemoveAllBackends -> ShowS
[RemoveAllBackends] -> ShowS
RemoveAllBackends -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveAllBackends] -> ShowS
$cshowList :: [RemoveAllBackends] -> ShowS
show :: RemoveAllBackends -> String
$cshow :: RemoveAllBackends -> String
showsPrec :: Int -> RemoveAllBackends -> ShowS
$cshowsPrec :: Int -> RemoveAllBackends -> ShowS
Prelude.Show, forall x. Rep RemoveAllBackends x -> RemoveAllBackends
forall x. RemoveAllBackends -> Rep RemoveAllBackends x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveAllBackends x -> RemoveAllBackends
$cfrom :: forall x. RemoveAllBackends -> Rep RemoveAllBackends x
Prelude.Generic)

-- |
-- Create a value of 'RemoveAllBackends' 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:
--
-- 'cleanAmplifyApp', 'removeAllBackends_cleanAmplifyApp' - Cleans up the Amplify Console app if this value is set to true.
--
-- 'appId', 'removeAllBackends_appId' - The app ID.
newRemoveAllBackends ::
  -- | 'appId'
  Prelude.Text ->
  RemoveAllBackends
newRemoveAllBackends :: Text -> RemoveAllBackends
newRemoveAllBackends Text
pAppId_ =
  RemoveAllBackends'
    { $sel:cleanAmplifyApp:RemoveAllBackends' :: Maybe Bool
cleanAmplifyApp =
        forall a. Maybe a
Prelude.Nothing,
      $sel:appId:RemoveAllBackends' :: Text
appId = Text
pAppId_
    }

-- | Cleans up the Amplify Console app if this value is set to true.
removeAllBackends_cleanAmplifyApp :: Lens.Lens' RemoveAllBackends (Prelude.Maybe Prelude.Bool)
removeAllBackends_cleanAmplifyApp :: Lens' RemoveAllBackends (Maybe Bool)
removeAllBackends_cleanAmplifyApp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveAllBackends' {Maybe Bool
cleanAmplifyApp :: Maybe Bool
$sel:cleanAmplifyApp:RemoveAllBackends' :: RemoveAllBackends -> Maybe Bool
cleanAmplifyApp} -> Maybe Bool
cleanAmplifyApp) (\s :: RemoveAllBackends
s@RemoveAllBackends' {} Maybe Bool
a -> RemoveAllBackends
s {$sel:cleanAmplifyApp:RemoveAllBackends' :: Maybe Bool
cleanAmplifyApp = Maybe Bool
a} :: RemoveAllBackends)

-- | The app ID.
removeAllBackends_appId :: Lens.Lens' RemoveAllBackends Prelude.Text
removeAllBackends_appId :: Lens' RemoveAllBackends Text
removeAllBackends_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveAllBackends' {Text
appId :: Text
$sel:appId:RemoveAllBackends' :: RemoveAllBackends -> Text
appId} -> Text
appId) (\s :: RemoveAllBackends
s@RemoveAllBackends' {} Text
a -> RemoveAllBackends
s {$sel:appId:RemoveAllBackends' :: Text
appId = Text
a} :: RemoveAllBackends)

instance Core.AWSRequest RemoveAllBackends where
  type
    AWSResponse RemoveAllBackends =
      RemoveAllBackendsResponse
  request :: (Service -> Service)
-> RemoveAllBackends -> Request RemoveAllBackends
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 RemoveAllBackends
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RemoveAllBackends)))
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
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> RemoveAllBackendsResponse
RemoveAllBackendsResponse'
            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
"appId")
            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
"error")
            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
"jobId")
            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
"operation")
            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
"status")
            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 RemoveAllBackends where
  hashWithSalt :: Int -> RemoveAllBackends -> Int
hashWithSalt Int
_salt RemoveAllBackends' {Maybe Bool
Text
appId :: Text
cleanAmplifyApp :: Maybe Bool
$sel:appId:RemoveAllBackends' :: RemoveAllBackends -> Text
$sel:cleanAmplifyApp:RemoveAllBackends' :: RemoveAllBackends -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
cleanAmplifyApp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId

instance Prelude.NFData RemoveAllBackends where
  rnf :: RemoveAllBackends -> ()
rnf RemoveAllBackends' {Maybe Bool
Text
appId :: Text
cleanAmplifyApp :: Maybe Bool
$sel:appId:RemoveAllBackends' :: RemoveAllBackends -> Text
$sel:cleanAmplifyApp:RemoveAllBackends' :: RemoveAllBackends -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
cleanAmplifyApp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appId

instance Data.ToHeaders RemoveAllBackends where
  toHeaders :: RemoveAllBackends -> 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 RemoveAllBackends where
  toJSON :: RemoveAllBackends -> Value
toJSON RemoveAllBackends' {Maybe Bool
Text
appId :: Text
cleanAmplifyApp :: Maybe Bool
$sel:appId:RemoveAllBackends' :: RemoveAllBackends -> Text
$sel:cleanAmplifyApp:RemoveAllBackends' :: RemoveAllBackends -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"cleanAmplifyApp" 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 Bool
cleanAmplifyApp
          ]
      )

instance Data.ToPath RemoveAllBackends where
  toPath :: RemoveAllBackends -> ByteString
toPath RemoveAllBackends' {Maybe Bool
Text
appId :: Text
cleanAmplifyApp :: Maybe Bool
$sel:appId:RemoveAllBackends' :: RemoveAllBackends -> Text
$sel:cleanAmplifyApp:RemoveAllBackends' :: RemoveAllBackends -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/backend/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId, ByteString
"/remove"]

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

-- | /See:/ 'newRemoveAllBackendsResponse' smart constructor.
data RemoveAllBackendsResponse = RemoveAllBackendsResponse'
  { -- | The app ID.
    RemoveAllBackendsResponse -> Maybe Text
appId :: Prelude.Maybe Prelude.Text,
    -- | If the request fails, this error is returned.
    RemoveAllBackendsResponse -> Maybe Text
error :: Prelude.Maybe Prelude.Text,
    -- | The ID for the job.
    RemoveAllBackendsResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The name of the operation.
    RemoveAllBackendsResponse -> Maybe Text
operation :: Prelude.Maybe Prelude.Text,
    -- | The current status of the request.
    RemoveAllBackendsResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RemoveAllBackendsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RemoveAllBackendsResponse -> RemoveAllBackendsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveAllBackendsResponse -> RemoveAllBackendsResponse -> Bool
$c/= :: RemoveAllBackendsResponse -> RemoveAllBackendsResponse -> Bool
== :: RemoveAllBackendsResponse -> RemoveAllBackendsResponse -> Bool
$c== :: RemoveAllBackendsResponse -> RemoveAllBackendsResponse -> Bool
Prelude.Eq, ReadPrec [RemoveAllBackendsResponse]
ReadPrec RemoveAllBackendsResponse
Int -> ReadS RemoveAllBackendsResponse
ReadS [RemoveAllBackendsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveAllBackendsResponse]
$creadListPrec :: ReadPrec [RemoveAllBackendsResponse]
readPrec :: ReadPrec RemoveAllBackendsResponse
$creadPrec :: ReadPrec RemoveAllBackendsResponse
readList :: ReadS [RemoveAllBackendsResponse]
$creadList :: ReadS [RemoveAllBackendsResponse]
readsPrec :: Int -> ReadS RemoveAllBackendsResponse
$creadsPrec :: Int -> ReadS RemoveAllBackendsResponse
Prelude.Read, Int -> RemoveAllBackendsResponse -> ShowS
[RemoveAllBackendsResponse] -> ShowS
RemoveAllBackendsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveAllBackendsResponse] -> ShowS
$cshowList :: [RemoveAllBackendsResponse] -> ShowS
show :: RemoveAllBackendsResponse -> String
$cshow :: RemoveAllBackendsResponse -> String
showsPrec :: Int -> RemoveAllBackendsResponse -> ShowS
$cshowsPrec :: Int -> RemoveAllBackendsResponse -> ShowS
Prelude.Show, forall x.
Rep RemoveAllBackendsResponse x -> RemoveAllBackendsResponse
forall x.
RemoveAllBackendsResponse -> Rep RemoveAllBackendsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoveAllBackendsResponse x -> RemoveAllBackendsResponse
$cfrom :: forall x.
RemoveAllBackendsResponse -> Rep RemoveAllBackendsResponse x
Prelude.Generic)

-- |
-- Create a value of 'RemoveAllBackendsResponse' 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:
--
-- 'appId', 'removeAllBackendsResponse_appId' - The app ID.
--
-- 'error', 'removeAllBackendsResponse_error' - If the request fails, this error is returned.
--
-- 'jobId', 'removeAllBackendsResponse_jobId' - The ID for the job.
--
-- 'operation', 'removeAllBackendsResponse_operation' - The name of the operation.
--
-- 'status', 'removeAllBackendsResponse_status' - The current status of the request.
--
-- 'httpStatus', 'removeAllBackendsResponse_httpStatus' - The response's http status code.
newRemoveAllBackendsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RemoveAllBackendsResponse
newRemoveAllBackendsResponse :: Int -> RemoveAllBackendsResponse
newRemoveAllBackendsResponse Int
pHttpStatus_ =
  RemoveAllBackendsResponse'
    { $sel:appId:RemoveAllBackendsResponse' :: Maybe Text
appId = forall a. Maybe a
Prelude.Nothing,
      $sel:error:RemoveAllBackendsResponse' :: Maybe Text
error = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:RemoveAllBackendsResponse' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:operation:RemoveAllBackendsResponse' :: Maybe Text
operation = forall a. Maybe a
Prelude.Nothing,
      $sel:status:RemoveAllBackendsResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RemoveAllBackendsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The app ID.
removeAllBackendsResponse_appId :: Lens.Lens' RemoveAllBackendsResponse (Prelude.Maybe Prelude.Text)
removeAllBackendsResponse_appId :: Lens' RemoveAllBackendsResponse (Maybe Text)
removeAllBackendsResponse_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveAllBackendsResponse' {Maybe Text
appId :: Maybe Text
$sel:appId:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
appId} -> Maybe Text
appId) (\s :: RemoveAllBackendsResponse
s@RemoveAllBackendsResponse' {} Maybe Text
a -> RemoveAllBackendsResponse
s {$sel:appId:RemoveAllBackendsResponse' :: Maybe Text
appId = Maybe Text
a} :: RemoveAllBackendsResponse)

-- | If the request fails, this error is returned.
removeAllBackendsResponse_error :: Lens.Lens' RemoveAllBackendsResponse (Prelude.Maybe Prelude.Text)
removeAllBackendsResponse_error :: Lens' RemoveAllBackendsResponse (Maybe Text)
removeAllBackendsResponse_error = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveAllBackendsResponse' {Maybe Text
error :: Maybe Text
$sel:error:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
error} -> Maybe Text
error) (\s :: RemoveAllBackendsResponse
s@RemoveAllBackendsResponse' {} Maybe Text
a -> RemoveAllBackendsResponse
s {$sel:error:RemoveAllBackendsResponse' :: Maybe Text
error = Maybe Text
a} :: RemoveAllBackendsResponse)

-- | The ID for the job.
removeAllBackendsResponse_jobId :: Lens.Lens' RemoveAllBackendsResponse (Prelude.Maybe Prelude.Text)
removeAllBackendsResponse_jobId :: Lens' RemoveAllBackendsResponse (Maybe Text)
removeAllBackendsResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveAllBackendsResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: RemoveAllBackendsResponse
s@RemoveAllBackendsResponse' {} Maybe Text
a -> RemoveAllBackendsResponse
s {$sel:jobId:RemoveAllBackendsResponse' :: Maybe Text
jobId = Maybe Text
a} :: RemoveAllBackendsResponse)

-- | The name of the operation.
removeAllBackendsResponse_operation :: Lens.Lens' RemoveAllBackendsResponse (Prelude.Maybe Prelude.Text)
removeAllBackendsResponse_operation :: Lens' RemoveAllBackendsResponse (Maybe Text)
removeAllBackendsResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveAllBackendsResponse' {Maybe Text
operation :: Maybe Text
$sel:operation:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
operation} -> Maybe Text
operation) (\s :: RemoveAllBackendsResponse
s@RemoveAllBackendsResponse' {} Maybe Text
a -> RemoveAllBackendsResponse
s {$sel:operation:RemoveAllBackendsResponse' :: Maybe Text
operation = Maybe Text
a} :: RemoveAllBackendsResponse)

-- | The current status of the request.
removeAllBackendsResponse_status :: Lens.Lens' RemoveAllBackendsResponse (Prelude.Maybe Prelude.Text)
removeAllBackendsResponse_status :: Lens' RemoveAllBackendsResponse (Maybe Text)
removeAllBackendsResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveAllBackendsResponse' {Maybe Text
status :: Maybe Text
$sel:status:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: RemoveAllBackendsResponse
s@RemoveAllBackendsResponse' {} Maybe Text
a -> RemoveAllBackendsResponse
s {$sel:status:RemoveAllBackendsResponse' :: Maybe Text
status = Maybe Text
a} :: RemoveAllBackendsResponse)

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

instance Prelude.NFData RemoveAllBackendsResponse where
  rnf :: RemoveAllBackendsResponse -> ()
rnf RemoveAllBackendsResponse' {Int
Maybe Text
httpStatus :: Int
status :: Maybe Text
operation :: Maybe Text
jobId :: Maybe Text
error :: Maybe Text
appId :: Maybe Text
$sel:httpStatus:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Int
$sel:status:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
$sel:operation:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
$sel:jobId:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
$sel:error:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
$sel:appId:RemoveAllBackendsResponse' :: RemoveAllBackendsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
error
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus