{-# 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.IAM.DeleteInstanceProfile
-- 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 instance profile. The instance profile must not
-- have an associated role.
--
-- Make sure that you do not have any Amazon EC2 instances running with the
-- instance profile you are about to delete. Deleting a role or instance
-- profile that is associated with a running instance will break any
-- applications running on the instance.
--
-- For more information about instance profiles, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/AboutInstanceProfiles.html About instance profiles>.
module Amazonka.IAM.DeleteInstanceProfile
  ( -- * Creating a Request
    DeleteInstanceProfile (..),
    newDeleteInstanceProfile,

    -- * Request Lenses
    deleteInstanceProfile_instanceProfileName,

    -- * Destructuring the Response
    DeleteInstanceProfileResponse (..),
    newDeleteInstanceProfileResponse,
  )
where

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

-- | /See:/ 'newDeleteInstanceProfile' smart constructor.
data DeleteInstanceProfile = DeleteInstanceProfile'
  { -- | The name of the instance profile to delete.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- consisting of upper and lowercase alphanumeric characters with no
    -- spaces. You can also include any of the following characters: _+=,.\@-
    DeleteInstanceProfile -> Text
instanceProfileName :: Prelude.Text
  }
  deriving (DeleteInstanceProfile -> DeleteInstanceProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteInstanceProfile -> DeleteInstanceProfile -> Bool
$c/= :: DeleteInstanceProfile -> DeleteInstanceProfile -> Bool
== :: DeleteInstanceProfile -> DeleteInstanceProfile -> Bool
$c== :: DeleteInstanceProfile -> DeleteInstanceProfile -> Bool
Prelude.Eq, ReadPrec [DeleteInstanceProfile]
ReadPrec DeleteInstanceProfile
Int -> ReadS DeleteInstanceProfile
ReadS [DeleteInstanceProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteInstanceProfile]
$creadListPrec :: ReadPrec [DeleteInstanceProfile]
readPrec :: ReadPrec DeleteInstanceProfile
$creadPrec :: ReadPrec DeleteInstanceProfile
readList :: ReadS [DeleteInstanceProfile]
$creadList :: ReadS [DeleteInstanceProfile]
readsPrec :: Int -> ReadS DeleteInstanceProfile
$creadsPrec :: Int -> ReadS DeleteInstanceProfile
Prelude.Read, Int -> DeleteInstanceProfile -> ShowS
[DeleteInstanceProfile] -> ShowS
DeleteInstanceProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteInstanceProfile] -> ShowS
$cshowList :: [DeleteInstanceProfile] -> ShowS
show :: DeleteInstanceProfile -> String
$cshow :: DeleteInstanceProfile -> String
showsPrec :: Int -> DeleteInstanceProfile -> ShowS
$cshowsPrec :: Int -> DeleteInstanceProfile -> ShowS
Prelude.Show, forall x. Rep DeleteInstanceProfile x -> DeleteInstanceProfile
forall x. DeleteInstanceProfile -> Rep DeleteInstanceProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteInstanceProfile x -> DeleteInstanceProfile
$cfrom :: forall x. DeleteInstanceProfile -> Rep DeleteInstanceProfile x
Prelude.Generic)

-- |
-- Create a value of 'DeleteInstanceProfile' 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:
--
-- 'instanceProfileName', 'deleteInstanceProfile_instanceProfileName' - The name of the instance profile to delete.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
newDeleteInstanceProfile ::
  -- | 'instanceProfileName'
  Prelude.Text ->
  DeleteInstanceProfile
newDeleteInstanceProfile :: Text -> DeleteInstanceProfile
newDeleteInstanceProfile Text
pInstanceProfileName_ =
  DeleteInstanceProfile'
    { $sel:instanceProfileName:DeleteInstanceProfile' :: Text
instanceProfileName =
        Text
pInstanceProfileName_
    }

-- | The name of the instance profile to delete.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
deleteInstanceProfile_instanceProfileName :: Lens.Lens' DeleteInstanceProfile Prelude.Text
deleteInstanceProfile_instanceProfileName :: Lens' DeleteInstanceProfile Text
deleteInstanceProfile_instanceProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstanceProfile' {Text
instanceProfileName :: Text
$sel:instanceProfileName:DeleteInstanceProfile' :: DeleteInstanceProfile -> Text
instanceProfileName} -> Text
instanceProfileName) (\s :: DeleteInstanceProfile
s@DeleteInstanceProfile' {} Text
a -> DeleteInstanceProfile
s {$sel:instanceProfileName:DeleteInstanceProfile' :: Text
instanceProfileName = Text
a} :: DeleteInstanceProfile)

instance Core.AWSRequest DeleteInstanceProfile where
  type
    AWSResponse DeleteInstanceProfile =
      DeleteInstanceProfileResponse
  request :: (Service -> Service)
-> DeleteInstanceProfile -> Request DeleteInstanceProfile
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteInstanceProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteInstanceProfile)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteInstanceProfileResponse
DeleteInstanceProfileResponse'

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

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

instance Data.ToHeaders DeleteInstanceProfile where
  toHeaders :: DeleteInstanceProfile -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DeleteInstanceProfile where
  toQuery :: DeleteInstanceProfile -> QueryString
toQuery DeleteInstanceProfile' {Text
instanceProfileName :: Text
$sel:instanceProfileName:DeleteInstanceProfile' :: DeleteInstanceProfile -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteInstanceProfile" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"InstanceProfileName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceProfileName
      ]

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

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

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