{-# 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.CodeDeploy.DeleteApplication
-- 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 an application.
module Amazonka.CodeDeploy.DeleteApplication
  ( -- * Creating a Request
    DeleteApplication (..),
    newDeleteApplication,

    -- * Request Lenses
    deleteApplication_applicationName,

    -- * Destructuring the Response
    DeleteApplicationResponse (..),
    newDeleteApplicationResponse,
  )
where

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

-- | Represents the input of a @DeleteApplication@ operation.
--
-- /See:/ 'newDeleteApplication' smart constructor.
data DeleteApplication = DeleteApplication'
  { -- | The name of an CodeDeploy application associated with the IAM user or
    -- Amazon Web Services account.
    DeleteApplication -> Text
applicationName :: Prelude.Text
  }
  deriving (DeleteApplication -> DeleteApplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteApplication -> DeleteApplication -> Bool
$c/= :: DeleteApplication -> DeleteApplication -> Bool
== :: DeleteApplication -> DeleteApplication -> Bool
$c== :: DeleteApplication -> DeleteApplication -> Bool
Prelude.Eq, ReadPrec [DeleteApplication]
ReadPrec DeleteApplication
Int -> ReadS DeleteApplication
ReadS [DeleteApplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteApplication]
$creadListPrec :: ReadPrec [DeleteApplication]
readPrec :: ReadPrec DeleteApplication
$creadPrec :: ReadPrec DeleteApplication
readList :: ReadS [DeleteApplication]
$creadList :: ReadS [DeleteApplication]
readsPrec :: Int -> ReadS DeleteApplication
$creadsPrec :: Int -> ReadS DeleteApplication
Prelude.Read, Int -> DeleteApplication -> ShowS
[DeleteApplication] -> ShowS
DeleteApplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteApplication] -> ShowS
$cshowList :: [DeleteApplication] -> ShowS
show :: DeleteApplication -> String
$cshow :: DeleteApplication -> String
showsPrec :: Int -> DeleteApplication -> ShowS
$cshowsPrec :: Int -> DeleteApplication -> ShowS
Prelude.Show, forall x. Rep DeleteApplication x -> DeleteApplication
forall x. DeleteApplication -> Rep DeleteApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteApplication x -> DeleteApplication
$cfrom :: forall x. DeleteApplication -> Rep DeleteApplication x
Prelude.Generic)

-- |
-- Create a value of 'DeleteApplication' 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:
--
-- 'applicationName', 'deleteApplication_applicationName' - The name of an CodeDeploy application associated with the IAM user or
-- Amazon Web Services account.
newDeleteApplication ::
  -- | 'applicationName'
  Prelude.Text ->
  DeleteApplication
newDeleteApplication :: Text -> DeleteApplication
newDeleteApplication Text
pApplicationName_ =
  DeleteApplication'
    { $sel:applicationName:DeleteApplication' :: Text
applicationName =
        Text
pApplicationName_
    }

-- | The name of an CodeDeploy application associated with the IAM user or
-- Amazon Web Services account.
deleteApplication_applicationName :: Lens.Lens' DeleteApplication Prelude.Text
deleteApplication_applicationName :: Lens' DeleteApplication Text
deleteApplication_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApplication' {Text
applicationName :: Text
$sel:applicationName:DeleteApplication' :: DeleteApplication -> Text
applicationName} -> Text
applicationName) (\s :: DeleteApplication
s@DeleteApplication' {} Text
a -> DeleteApplication
s {$sel:applicationName:DeleteApplication' :: Text
applicationName = Text
a} :: DeleteApplication)

instance Core.AWSRequest DeleteApplication where
  type
    AWSResponse DeleteApplication =
      DeleteApplicationResponse
  request :: (Service -> Service)
-> DeleteApplication -> Request DeleteApplication
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 DeleteApplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteApplication)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteApplicationResponse
DeleteApplicationResponse'

instance Prelude.Hashable DeleteApplication where
  hashWithSalt :: Int -> DeleteApplication -> Int
hashWithSalt Int
_salt DeleteApplication' {Text
applicationName :: Text
$sel:applicationName:DeleteApplication' :: DeleteApplication -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationName

instance Prelude.NFData DeleteApplication where
  rnf :: DeleteApplication -> ()
rnf DeleteApplication' {Text
applicationName :: Text
$sel:applicationName:DeleteApplication' :: DeleteApplication -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationName

instance Data.ToHeaders DeleteApplication where
  toHeaders :: DeleteApplication -> [Header]
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 -> [Header]
Data.=# ( ByteString
"CodeDeploy_20141006.DeleteApplication" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteApplication where
  toJSON :: DeleteApplication -> Value
toJSON DeleteApplication' {Text
applicationName :: Text
$sel:applicationName:DeleteApplication' :: DeleteApplication -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"applicationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
applicationName)
          ]
      )

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

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

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

-- |
-- Create a value of 'DeleteApplicationResponse' 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.
newDeleteApplicationResponse ::
  DeleteApplicationResponse
newDeleteApplicationResponse :: DeleteApplicationResponse
newDeleteApplicationResponse =
  DeleteApplicationResponse
DeleteApplicationResponse'

instance Prelude.NFData DeleteApplicationResponse where
  rnf :: DeleteApplicationResponse -> ()
rnf DeleteApplicationResponse
_ = ()