{-# 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.IoT.DetachPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Detaches a policy from the specified target.
--
-- Because of the distributed nature of Amazon Web Services, it can take up
-- to five minutes after a policy is detached before it\'s ready to be
-- deleted.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions DetachPolicy>
-- action.
module Amazonka.IoT.DetachPolicy
  ( -- * Creating a Request
    DetachPolicy (..),
    newDetachPolicy,

    -- * Request Lenses
    detachPolicy_policyName,
    detachPolicy_target,

    -- * Destructuring the Response
    DetachPolicyResponse (..),
    newDetachPolicyResponse,
  )
where

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

-- | /See:/ 'newDetachPolicy' smart constructor.
data DetachPolicy = DetachPolicy'
  { -- | The policy to detach.
    DetachPolicy -> Text
policyName :: Prelude.Text,
    -- | The target from which the policy will be detached.
    DetachPolicy -> Text
target :: Prelude.Text
  }
  deriving (DetachPolicy -> DetachPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachPolicy -> DetachPolicy -> Bool
$c/= :: DetachPolicy -> DetachPolicy -> Bool
== :: DetachPolicy -> DetachPolicy -> Bool
$c== :: DetachPolicy -> DetachPolicy -> Bool
Prelude.Eq, ReadPrec [DetachPolicy]
ReadPrec DetachPolicy
Int -> ReadS DetachPolicy
ReadS [DetachPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachPolicy]
$creadListPrec :: ReadPrec [DetachPolicy]
readPrec :: ReadPrec DetachPolicy
$creadPrec :: ReadPrec DetachPolicy
readList :: ReadS [DetachPolicy]
$creadList :: ReadS [DetachPolicy]
readsPrec :: Int -> ReadS DetachPolicy
$creadsPrec :: Int -> ReadS DetachPolicy
Prelude.Read, Int -> DetachPolicy -> ShowS
[DetachPolicy] -> ShowS
DetachPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachPolicy] -> ShowS
$cshowList :: [DetachPolicy] -> ShowS
show :: DetachPolicy -> String
$cshow :: DetachPolicy -> String
showsPrec :: Int -> DetachPolicy -> ShowS
$cshowsPrec :: Int -> DetachPolicy -> ShowS
Prelude.Show, forall x. Rep DetachPolicy x -> DetachPolicy
forall x. DetachPolicy -> Rep DetachPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachPolicy x -> DetachPolicy
$cfrom :: forall x. DetachPolicy -> Rep DetachPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DetachPolicy' 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:
--
-- 'policyName', 'detachPolicy_policyName' - The policy to detach.
--
-- 'target', 'detachPolicy_target' - The target from which the policy will be detached.
newDetachPolicy ::
  -- | 'policyName'
  Prelude.Text ->
  -- | 'target'
  Prelude.Text ->
  DetachPolicy
newDetachPolicy :: Text -> Text -> DetachPolicy
newDetachPolicy Text
pPolicyName_ Text
pTarget_ =
  DetachPolicy'
    { $sel:policyName:DetachPolicy' :: Text
policyName = Text
pPolicyName_,
      $sel:target:DetachPolicy' :: Text
target = Text
pTarget_
    }

-- | The policy to detach.
detachPolicy_policyName :: Lens.Lens' DetachPolicy Prelude.Text
detachPolicy_policyName :: Lens' DetachPolicy Text
detachPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachPolicy' {Text
policyName :: Text
$sel:policyName:DetachPolicy' :: DetachPolicy -> Text
policyName} -> Text
policyName) (\s :: DetachPolicy
s@DetachPolicy' {} Text
a -> DetachPolicy
s {$sel:policyName:DetachPolicy' :: Text
policyName = Text
a} :: DetachPolicy)

-- | The target from which the policy will be detached.
detachPolicy_target :: Lens.Lens' DetachPolicy Prelude.Text
detachPolicy_target :: Lens' DetachPolicy Text
detachPolicy_target = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachPolicy' {Text
target :: Text
$sel:target:DetachPolicy' :: DetachPolicy -> Text
target} -> Text
target) (\s :: DetachPolicy
s@DetachPolicy' {} Text
a -> DetachPolicy
s {$sel:target:DetachPolicy' :: Text
target = Text
a} :: DetachPolicy)

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

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

instance Prelude.NFData DetachPolicy where
  rnf :: DetachPolicy -> ()
rnf DetachPolicy' {Text
target :: Text
policyName :: Text
$sel:target:DetachPolicy' :: DetachPolicy -> Text
$sel:policyName:DetachPolicy' :: DetachPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
target

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

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

instance Data.ToPath DetachPolicy where
  toPath :: DetachPolicy -> ByteString
toPath DetachPolicy' {Text
target :: Text
policyName :: Text
$sel:target:DetachPolicy' :: DetachPolicy -> Text
$sel:policyName:DetachPolicy' :: DetachPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/target-policies/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyName]

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

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

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

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