{-# 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.SMS.DeleteApp
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the specified application. Optionally deletes the launched stack
-- associated with the application and all Server Migration Service
-- replication jobs for servers in the application.
module Amazonka.SMS.DeleteApp
  ( -- * Creating a Request
    DeleteApp (..),
    newDeleteApp,

    -- * Request Lenses
    deleteApp_appId,
    deleteApp_forceStopAppReplication,
    deleteApp_forceTerminateApp,

    -- * Destructuring the Response
    DeleteAppResponse (..),
    newDeleteAppResponse,

    -- * Response Lenses
    deleteAppResponse_httpStatus,
  )
where

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
import Amazonka.SMS.Types

-- | /See:/ 'newDeleteApp' smart constructor.
data DeleteApp = DeleteApp'
  { -- | The ID of the application.
    DeleteApp -> Maybe Text
appId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether to stop all replication jobs corresponding to the
    -- servers in the application while deleting the application.
    DeleteApp -> Maybe Bool
forceStopAppReplication :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether to terminate the stack corresponding to the
    -- application while deleting the application.
    DeleteApp -> Maybe Bool
forceTerminateApp :: Prelude.Maybe Prelude.Bool
  }
  deriving (DeleteApp -> DeleteApp -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteApp -> DeleteApp -> Bool
$c/= :: DeleteApp -> DeleteApp -> Bool
== :: DeleteApp -> DeleteApp -> Bool
$c== :: DeleteApp -> DeleteApp -> Bool
Prelude.Eq, ReadPrec [DeleteApp]
ReadPrec DeleteApp
Int -> ReadS DeleteApp
ReadS [DeleteApp]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteApp]
$creadListPrec :: ReadPrec [DeleteApp]
readPrec :: ReadPrec DeleteApp
$creadPrec :: ReadPrec DeleteApp
readList :: ReadS [DeleteApp]
$creadList :: ReadS [DeleteApp]
readsPrec :: Int -> ReadS DeleteApp
$creadsPrec :: Int -> ReadS DeleteApp
Prelude.Read, Int -> DeleteApp -> ShowS
[DeleteApp] -> ShowS
DeleteApp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteApp] -> ShowS
$cshowList :: [DeleteApp] -> ShowS
show :: DeleteApp -> String
$cshow :: DeleteApp -> String
showsPrec :: Int -> DeleteApp -> ShowS
$cshowsPrec :: Int -> DeleteApp -> ShowS
Prelude.Show, forall x. Rep DeleteApp x -> DeleteApp
forall x. DeleteApp -> Rep DeleteApp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteApp x -> DeleteApp
$cfrom :: forall x. DeleteApp -> Rep DeleteApp x
Prelude.Generic)

-- |
-- Create a value of 'DeleteApp' 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', 'deleteApp_appId' - The ID of the application.
--
-- 'forceStopAppReplication', 'deleteApp_forceStopAppReplication' - Indicates whether to stop all replication jobs corresponding to the
-- servers in the application while deleting the application.
--
-- 'forceTerminateApp', 'deleteApp_forceTerminateApp' - Indicates whether to terminate the stack corresponding to the
-- application while deleting the application.
newDeleteApp ::
  DeleteApp
newDeleteApp :: DeleteApp
newDeleteApp =
  DeleteApp'
    { $sel:appId:DeleteApp' :: Maybe Text
appId = forall a. Maybe a
Prelude.Nothing,
      $sel:forceStopAppReplication:DeleteApp' :: Maybe Bool
forceStopAppReplication = forall a. Maybe a
Prelude.Nothing,
      $sel:forceTerminateApp:DeleteApp' :: Maybe Bool
forceTerminateApp = forall a. Maybe a
Prelude.Nothing
    }

-- | The ID of the application.
deleteApp_appId :: Lens.Lens' DeleteApp (Prelude.Maybe Prelude.Text)
deleteApp_appId :: Lens' DeleteApp (Maybe Text)
deleteApp_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {Maybe Text
appId :: Maybe Text
$sel:appId:DeleteApp' :: DeleteApp -> Maybe Text
appId} -> Maybe Text
appId) (\s :: DeleteApp
s@DeleteApp' {} Maybe Text
a -> DeleteApp
s {$sel:appId:DeleteApp' :: Maybe Text
appId = Maybe Text
a} :: DeleteApp)

-- | Indicates whether to stop all replication jobs corresponding to the
-- servers in the application while deleting the application.
deleteApp_forceStopAppReplication :: Lens.Lens' DeleteApp (Prelude.Maybe Prelude.Bool)
deleteApp_forceStopAppReplication :: Lens' DeleteApp (Maybe Bool)
deleteApp_forceStopAppReplication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {Maybe Bool
forceStopAppReplication :: Maybe Bool
$sel:forceStopAppReplication:DeleteApp' :: DeleteApp -> Maybe Bool
forceStopAppReplication} -> Maybe Bool
forceStopAppReplication) (\s :: DeleteApp
s@DeleteApp' {} Maybe Bool
a -> DeleteApp
s {$sel:forceStopAppReplication:DeleteApp' :: Maybe Bool
forceStopAppReplication = Maybe Bool
a} :: DeleteApp)

-- | Indicates whether to terminate the stack corresponding to the
-- application while deleting the application.
deleteApp_forceTerminateApp :: Lens.Lens' DeleteApp (Prelude.Maybe Prelude.Bool)
deleteApp_forceTerminateApp :: Lens' DeleteApp (Maybe Bool)
deleteApp_forceTerminateApp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {Maybe Bool
forceTerminateApp :: Maybe Bool
$sel:forceTerminateApp:DeleteApp' :: DeleteApp -> Maybe Bool
forceTerminateApp} -> Maybe Bool
forceTerminateApp) (\s :: DeleteApp
s@DeleteApp' {} Maybe Bool
a -> DeleteApp
s {$sel:forceTerminateApp:DeleteApp' :: Maybe Bool
forceTerminateApp = Maybe Bool
a} :: DeleteApp)

instance Core.AWSRequest DeleteApp where
  type AWSResponse DeleteApp = DeleteAppResponse
  request :: (Service -> Service) -> DeleteApp -> Request DeleteApp
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 DeleteApp
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteApp)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteAppResponse
DeleteAppResponse'
            forall (f :: * -> *) a b. Functor 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 DeleteApp where
  hashWithSalt :: Int -> DeleteApp -> Int
hashWithSalt Int
_salt DeleteApp' {Maybe Bool
Maybe Text
forceTerminateApp :: Maybe Bool
forceStopAppReplication :: Maybe Bool
appId :: Maybe Text
$sel:forceTerminateApp:DeleteApp' :: DeleteApp -> Maybe Bool
$sel:forceStopAppReplication:DeleteApp' :: DeleteApp -> Maybe Bool
$sel:appId:DeleteApp' :: DeleteApp -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
appId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
forceStopAppReplication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
forceTerminateApp

instance Prelude.NFData DeleteApp where
  rnf :: DeleteApp -> ()
rnf DeleteApp' {Maybe Bool
Maybe Text
forceTerminateApp :: Maybe Bool
forceStopAppReplication :: Maybe Bool
appId :: Maybe Text
$sel:forceTerminateApp:DeleteApp' :: DeleteApp -> Maybe Bool
$sel:forceStopAppReplication:DeleteApp' :: DeleteApp -> Maybe Bool
$sel:appId:DeleteApp' :: DeleteApp -> 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 Bool
forceStopAppReplication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
forceTerminateApp

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

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

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

-- | /See:/ 'newDeleteAppResponse' smart constructor.
data DeleteAppResponse = DeleteAppResponse'
  { -- | The response's http status code.
    DeleteAppResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteAppResponse -> DeleteAppResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAppResponse -> DeleteAppResponse -> Bool
$c/= :: DeleteAppResponse -> DeleteAppResponse -> Bool
== :: DeleteAppResponse -> DeleteAppResponse -> Bool
$c== :: DeleteAppResponse -> DeleteAppResponse -> Bool
Prelude.Eq, ReadPrec [DeleteAppResponse]
ReadPrec DeleteAppResponse
Int -> ReadS DeleteAppResponse
ReadS [DeleteAppResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAppResponse]
$creadListPrec :: ReadPrec [DeleteAppResponse]
readPrec :: ReadPrec DeleteAppResponse
$creadPrec :: ReadPrec DeleteAppResponse
readList :: ReadS [DeleteAppResponse]
$creadList :: ReadS [DeleteAppResponse]
readsPrec :: Int -> ReadS DeleteAppResponse
$creadsPrec :: Int -> ReadS DeleteAppResponse
Prelude.Read, Int -> DeleteAppResponse -> ShowS
[DeleteAppResponse] -> ShowS
DeleteAppResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAppResponse] -> ShowS
$cshowList :: [DeleteAppResponse] -> ShowS
show :: DeleteAppResponse -> String
$cshow :: DeleteAppResponse -> String
showsPrec :: Int -> DeleteAppResponse -> ShowS
$cshowsPrec :: Int -> DeleteAppResponse -> ShowS
Prelude.Show, forall x. Rep DeleteAppResponse x -> DeleteAppResponse
forall x. DeleteAppResponse -> Rep DeleteAppResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAppResponse x -> DeleteAppResponse
$cfrom :: forall x. DeleteAppResponse -> Rep DeleteAppResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAppResponse' 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:
--
-- 'httpStatus', 'deleteAppResponse_httpStatus' - The response's http status code.
newDeleteAppResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteAppResponse
newDeleteAppResponse :: Int -> DeleteAppResponse
newDeleteAppResponse Int
pHttpStatus_ =
  DeleteAppResponse' {$sel:httpStatus:DeleteAppResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData DeleteAppResponse where
  rnf :: DeleteAppResponse -> ()
rnf DeleteAppResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteAppResponse' :: DeleteAppResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus