{-# 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.DetachUserPolicy
-- 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 the specified managed policy from the specified user.
--
-- A user can also have inline policies embedded with it. To delete an
-- inline policy, use DeleteUserPolicy. For information about policies, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
module Amazonka.IAM.DetachUserPolicy
  ( -- * Creating a Request
    DetachUserPolicy (..),
    newDetachUserPolicy,

    -- * Request Lenses
    detachUserPolicy_userName,
    detachUserPolicy_policyArn,

    -- * Destructuring the Response
    DetachUserPolicyResponse (..),
    newDetachUserPolicyResponse,
  )
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:/ 'newDetachUserPolicy' smart constructor.
data DetachUserPolicy = DetachUserPolicy'
  { -- | The name (friendly name, not ARN) of the IAM user to detach the policy
    -- from.
    --
    -- 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: _+=,.\@-
    DetachUserPolicy -> Text
userName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the IAM policy you want to detach.
    --
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /Amazon Web Services General Reference/.
    DetachUserPolicy -> Text
policyArn :: Prelude.Text
  }
  deriving (DetachUserPolicy -> DetachUserPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachUserPolicy -> DetachUserPolicy -> Bool
$c/= :: DetachUserPolicy -> DetachUserPolicy -> Bool
== :: DetachUserPolicy -> DetachUserPolicy -> Bool
$c== :: DetachUserPolicy -> DetachUserPolicy -> Bool
Prelude.Eq, ReadPrec [DetachUserPolicy]
ReadPrec DetachUserPolicy
Int -> ReadS DetachUserPolicy
ReadS [DetachUserPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachUserPolicy]
$creadListPrec :: ReadPrec [DetachUserPolicy]
readPrec :: ReadPrec DetachUserPolicy
$creadPrec :: ReadPrec DetachUserPolicy
readList :: ReadS [DetachUserPolicy]
$creadList :: ReadS [DetachUserPolicy]
readsPrec :: Int -> ReadS DetachUserPolicy
$creadsPrec :: Int -> ReadS DetachUserPolicy
Prelude.Read, Int -> DetachUserPolicy -> ShowS
[DetachUserPolicy] -> ShowS
DetachUserPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachUserPolicy] -> ShowS
$cshowList :: [DetachUserPolicy] -> ShowS
show :: DetachUserPolicy -> String
$cshow :: DetachUserPolicy -> String
showsPrec :: Int -> DetachUserPolicy -> ShowS
$cshowsPrec :: Int -> DetachUserPolicy -> ShowS
Prelude.Show, forall x. Rep DetachUserPolicy x -> DetachUserPolicy
forall x. DetachUserPolicy -> Rep DetachUserPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachUserPolicy x -> DetachUserPolicy
$cfrom :: forall x. DetachUserPolicy -> Rep DetachUserPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DetachUserPolicy' 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:
--
-- 'userName', 'detachUserPolicy_userName' - The name (friendly name, not ARN) of the IAM user to detach the policy
-- from.
--
-- 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: _+=,.\@-
--
-- 'policyArn', 'detachUserPolicy_policyArn' - The Amazon Resource Name (ARN) of the IAM policy you want to detach.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
newDetachUserPolicy ::
  -- | 'userName'
  Prelude.Text ->
  -- | 'policyArn'
  Prelude.Text ->
  DetachUserPolicy
newDetachUserPolicy :: Text -> Text -> DetachUserPolicy
newDetachUserPolicy Text
pUserName_ Text
pPolicyArn_ =
  DetachUserPolicy'
    { $sel:userName:DetachUserPolicy' :: Text
userName = Text
pUserName_,
      $sel:policyArn:DetachUserPolicy' :: Text
policyArn = Text
pPolicyArn_
    }

-- | The name (friendly name, not ARN) of the IAM user to detach the policy
-- from.
--
-- 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: _+=,.\@-
detachUserPolicy_userName :: Lens.Lens' DetachUserPolicy Prelude.Text
detachUserPolicy_userName :: Lens' DetachUserPolicy Text
detachUserPolicy_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachUserPolicy' {Text
userName :: Text
$sel:userName:DetachUserPolicy' :: DetachUserPolicy -> Text
userName} -> Text
userName) (\s :: DetachUserPolicy
s@DetachUserPolicy' {} Text
a -> DetachUserPolicy
s {$sel:userName:DetachUserPolicy' :: Text
userName = Text
a} :: DetachUserPolicy)

-- | The Amazon Resource Name (ARN) of the IAM policy you want to detach.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
detachUserPolicy_policyArn :: Lens.Lens' DetachUserPolicy Prelude.Text
detachUserPolicy_policyArn :: Lens' DetachUserPolicy Text
detachUserPolicy_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachUserPolicy' {Text
policyArn :: Text
$sel:policyArn:DetachUserPolicy' :: DetachUserPolicy -> Text
policyArn} -> Text
policyArn) (\s :: DetachUserPolicy
s@DetachUserPolicy' {} Text
a -> DetachUserPolicy
s {$sel:policyArn:DetachUserPolicy' :: Text
policyArn = Text
a} :: DetachUserPolicy)

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

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

instance Prelude.NFData DetachUserPolicy where
  rnf :: DetachUserPolicy -> ()
rnf DetachUserPolicy' {Text
policyArn :: Text
userName :: Text
$sel:policyArn:DetachUserPolicy' :: DetachUserPolicy -> Text
$sel:userName:DetachUserPolicy' :: DetachUserPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyArn

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

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

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

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

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

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