{-# 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.Organizations.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 a target root, organizational unit (OU), or
-- account.
--
-- If the policy being detached is a service control policy (SCP), the
-- changes to permissions for Identity and Access Management (IAM) users
-- and roles in affected accounts are immediate.
--
-- Every root, OU, and account must have at least one SCP attached. If you
-- want to replace the default @FullAWSAccess@ policy with an SCP that
-- limits the permissions that can be delegated, you must attach the
-- replacement SCP before you can remove the default SCP. This is the
-- authorization strategy of an
-- \"<https://docs.aws.amazon.com/organizations/latest/userguide/SCP_strategies.html#orgs_policies_allowlist allow list>\".
-- If you instead attach a second SCP and leave the @FullAWSAccess@ SCP
-- still attached, and specify @\"Effect\": \"Deny\"@ in the second SCP to
-- override the @\"Effect\": \"Allow\"@ in the @FullAWSAccess@ policy (or
-- any other attached SCP), you\'re using the authorization strategy of a
-- \"<https://docs.aws.amazon.com/organizations/latest/userguide/SCP_strategies.html#orgs_policies_denylist deny list>\".
--
-- This operation can be called only from the organization\'s management
-- account.
module Amazonka.Organizations.DetachPolicy
  ( -- * Creating a Request
    DetachPolicy (..),
    newDetachPolicy,

    -- * Request Lenses
    detachPolicy_policyId,
    detachPolicy_targetId,

    -- * 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.Organizations.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 unique identifier (ID) of the policy you want to detach. You can get
    -- the ID from the ListPolicies or ListPoliciesForTarget operations.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> for a policy ID
    -- string requires \"p-\" followed by from 8 to 128 lowercase or uppercase
    -- letters, digits, or the underscore character (_).
    DetachPolicy -> Text
policyId :: Prelude.Text,
    -- | The unique identifier (ID) of the root, OU, or account that you want to
    -- detach the policy from. You can get the ID from the ListRoots,
    -- ListOrganizationalUnitsForParent, or ListAccounts operations.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> for a target ID
    -- string requires one of the following:
    --
    -- -   __Root__ - A string that begins with \"r-\" followed by from 4 to 32
    --     lowercase letters or digits.
    --
    -- -   __Account__ - A string that consists of exactly 12 digits.
    --
    -- -   __Organizational unit (OU)__ - A string that begins with \"ou-\"
    --     followed by from 4 to 32 lowercase letters or digits (the ID of the
    --     root that the OU is in). This string is followed by a second \"-\"
    --     dash and from 8 to 32 additional lowercase letters or digits.
    DetachPolicy -> Text
targetId :: 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:
--
-- 'policyId', 'detachPolicy_policyId' - The unique identifier (ID) of the policy you want to detach. You can get
-- the ID from the ListPolicies or ListPoliciesForTarget operations.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a policy ID
-- string requires \"p-\" followed by from 8 to 128 lowercase or uppercase
-- letters, digits, or the underscore character (_).
--
-- 'targetId', 'detachPolicy_targetId' - The unique identifier (ID) of the root, OU, or account that you want to
-- detach the policy from. You can get the ID from the ListRoots,
-- ListOrganizationalUnitsForParent, or ListAccounts operations.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a target ID
-- string requires one of the following:
--
-- -   __Root__ - A string that begins with \"r-\" followed by from 4 to 32
--     lowercase letters or digits.
--
-- -   __Account__ - A string that consists of exactly 12 digits.
--
-- -   __Organizational unit (OU)__ - A string that begins with \"ou-\"
--     followed by from 4 to 32 lowercase letters or digits (the ID of the
--     root that the OU is in). This string is followed by a second \"-\"
--     dash and from 8 to 32 additional lowercase letters or digits.
newDetachPolicy ::
  -- | 'policyId'
  Prelude.Text ->
  -- | 'targetId'
  Prelude.Text ->
  DetachPolicy
newDetachPolicy :: Text -> Text -> DetachPolicy
newDetachPolicy Text
pPolicyId_ Text
pTargetId_ =
  DetachPolicy'
    { $sel:policyId:DetachPolicy' :: Text
policyId = Text
pPolicyId_,
      $sel:targetId:DetachPolicy' :: Text
targetId = Text
pTargetId_
    }

-- | The unique identifier (ID) of the policy you want to detach. You can get
-- the ID from the ListPolicies or ListPoliciesForTarget operations.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a policy ID
-- string requires \"p-\" followed by from 8 to 128 lowercase or uppercase
-- letters, digits, or the underscore character (_).
detachPolicy_policyId :: Lens.Lens' DetachPolicy Prelude.Text
detachPolicy_policyId :: Lens' DetachPolicy Text
detachPolicy_policyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachPolicy' {Text
policyId :: Text
$sel:policyId:DetachPolicy' :: DetachPolicy -> Text
policyId} -> Text
policyId) (\s :: DetachPolicy
s@DetachPolicy' {} Text
a -> DetachPolicy
s {$sel:policyId:DetachPolicy' :: Text
policyId = Text
a} :: DetachPolicy)

-- | The unique identifier (ID) of the root, OU, or account that you want to
-- detach the policy from. You can get the ID from the ListRoots,
-- ListOrganizationalUnitsForParent, or ListAccounts operations.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a target ID
-- string requires one of the following:
--
-- -   __Root__ - A string that begins with \"r-\" followed by from 4 to 32
--     lowercase letters or digits.
--
-- -   __Account__ - A string that consists of exactly 12 digits.
--
-- -   __Organizational unit (OU)__ - A string that begins with \"ou-\"
--     followed by from 4 to 32 lowercase letters or digits (the ID of the
--     root that the OU is in). This string is followed by a second \"-\"
--     dash and from 8 to 32 additional lowercase letters or digits.
detachPolicy_targetId :: Lens.Lens' DetachPolicy Prelude.Text
detachPolicy_targetId :: Lens' DetachPolicy Text
detachPolicy_targetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachPolicy' {Text
targetId :: Text
$sel:targetId:DetachPolicy' :: DetachPolicy -> Text
targetId} -> Text
targetId) (\s :: DetachPolicy
s@DetachPolicy' {} Text
a -> DetachPolicy
s {$sel:targetId:DetachPolicy' :: Text
targetId = 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
targetId :: Text
policyId :: Text
$sel:targetId:DetachPolicy' :: DetachPolicy -> Text
$sel:policyId:DetachPolicy' :: DetachPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetId

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

instance Data.ToHeaders DetachPolicy where
  toHeaders :: DetachPolicy -> [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
"AWSOrganizationsV20161128.DetachPolicy" ::
                          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 DetachPolicy where
  toJSON :: DetachPolicy -> Value
toJSON DetachPolicy' {Text
targetId :: Text
policyId :: Text
$sel:targetId:DetachPolicy' :: DetachPolicy -> Text
$sel:policyId:DetachPolicy' :: DetachPolicy -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"PolicyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
policyId),
            forall a. a -> Maybe a
Prelude.Just (Key
"TargetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
targetId)
          ]
      )

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

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
_ = ()