{-# 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.AttachPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Attaches a policy to a root, an organizational unit (OU), or an
-- individual account. How the policy affects accounts depends on the type
-- of policy. Refer to the /Organizations User Guide/ for information about
-- each policy type:
--
-- -   <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_manage_policies_ai-opt-out.html AISERVICES_OPT_OUT_POLICY>
--
-- -   <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_manage_policies_backup.html BACKUP_POLICY>
--
-- -   <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_manage_policies_scp.html SERVICE_CONTROL_POLICY>
--
-- -   <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_manage_policies_tag-policies.html TAG_POLICY>
--
-- This operation can be called only from the organization\'s management
-- account.
module Amazonka.Organizations.AttachPolicy
  ( -- * Creating a Request
    AttachPolicy (..),
    newAttachPolicy,

    -- * Request Lenses
    attachPolicy_policyId,
    attachPolicy_targetId,

    -- * Destructuring the Response
    AttachPolicyResponse (..),
    newAttachPolicyResponse,
  )
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:/ 'newAttachPolicy' smart constructor.
data AttachPolicy = AttachPolicy'
  { -- | The unique identifier (ID) of the policy that you want to attach to the
    -- target. You can get the ID for the policy by calling the ListPolicies
    -- operation.
    --
    -- 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 (_).
    AttachPolicy -> Text
policyId :: Prelude.Text,
    -- | The unique identifier (ID) of the root, OU, or account that you want to
    -- attach the policy to. You can get the ID by calling 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.
    AttachPolicy -> Text
targetId :: Prelude.Text
  }
  deriving (AttachPolicy -> AttachPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachPolicy -> AttachPolicy -> Bool
$c/= :: AttachPolicy -> AttachPolicy -> Bool
== :: AttachPolicy -> AttachPolicy -> Bool
$c== :: AttachPolicy -> AttachPolicy -> Bool
Prelude.Eq, ReadPrec [AttachPolicy]
ReadPrec AttachPolicy
Int -> ReadS AttachPolicy
ReadS [AttachPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachPolicy]
$creadListPrec :: ReadPrec [AttachPolicy]
readPrec :: ReadPrec AttachPolicy
$creadPrec :: ReadPrec AttachPolicy
readList :: ReadS [AttachPolicy]
$creadList :: ReadS [AttachPolicy]
readsPrec :: Int -> ReadS AttachPolicy
$creadsPrec :: Int -> ReadS AttachPolicy
Prelude.Read, Int -> AttachPolicy -> ShowS
[AttachPolicy] -> ShowS
AttachPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachPolicy] -> ShowS
$cshowList :: [AttachPolicy] -> ShowS
show :: AttachPolicy -> String
$cshow :: AttachPolicy -> String
showsPrec :: Int -> AttachPolicy -> ShowS
$cshowsPrec :: Int -> AttachPolicy -> ShowS
Prelude.Show, forall x. Rep AttachPolicy x -> AttachPolicy
forall x. AttachPolicy -> Rep AttachPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachPolicy x -> AttachPolicy
$cfrom :: forall x. AttachPolicy -> Rep AttachPolicy x
Prelude.Generic)

-- |
-- Create a value of 'AttachPolicy' 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', 'attachPolicy_policyId' - The unique identifier (ID) of the policy that you want to attach to the
-- target. You can get the ID for the policy by calling the ListPolicies
-- operation.
--
-- 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', 'attachPolicy_targetId' - The unique identifier (ID) of the root, OU, or account that you want to
-- attach the policy to. You can get the ID by calling 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.
newAttachPolicy ::
  -- | 'policyId'
  Prelude.Text ->
  -- | 'targetId'
  Prelude.Text ->
  AttachPolicy
newAttachPolicy :: Text -> Text -> AttachPolicy
newAttachPolicy Text
pPolicyId_ Text
pTargetId_ =
  AttachPolicy'
    { $sel:policyId:AttachPolicy' :: Text
policyId = Text
pPolicyId_,
      $sel:targetId:AttachPolicy' :: Text
targetId = Text
pTargetId_
    }

-- | The unique identifier (ID) of the policy that you want to attach to the
-- target. You can get the ID for the policy by calling the ListPolicies
-- operation.
--
-- 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 (_).
attachPolicy_policyId :: Lens.Lens' AttachPolicy Prelude.Text
attachPolicy_policyId :: Lens' AttachPolicy Text
attachPolicy_policyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachPolicy' {Text
policyId :: Text
$sel:policyId:AttachPolicy' :: AttachPolicy -> Text
policyId} -> Text
policyId) (\s :: AttachPolicy
s@AttachPolicy' {} Text
a -> AttachPolicy
s {$sel:policyId:AttachPolicy' :: Text
policyId = Text
a} :: AttachPolicy)

-- | The unique identifier (ID) of the root, OU, or account that you want to
-- attach the policy to. You can get the ID by calling 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.
attachPolicy_targetId :: Lens.Lens' AttachPolicy Prelude.Text
attachPolicy_targetId :: Lens' AttachPolicy Text
attachPolicy_targetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachPolicy' {Text
targetId :: Text
$sel:targetId:AttachPolicy' :: AttachPolicy -> Text
targetId} -> Text
targetId) (\s :: AttachPolicy
s@AttachPolicy' {} Text
a -> AttachPolicy
s {$sel:targetId:AttachPolicy' :: Text
targetId = Text
a} :: AttachPolicy)

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

instance Prelude.Hashable AttachPolicy where
  hashWithSalt :: Int -> AttachPolicy -> Int
hashWithSalt Int
_salt AttachPolicy' {Text
targetId :: Text
policyId :: Text
$sel:targetId:AttachPolicy' :: AttachPolicy -> Text
$sel:policyId:AttachPolicy' :: AttachPolicy -> 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 AttachPolicy where
  rnf :: AttachPolicy -> ()
rnf AttachPolicy' {Text
targetId :: Text
policyId :: Text
$sel:targetId:AttachPolicy' :: AttachPolicy -> Text
$sel:policyId:AttachPolicy' :: AttachPolicy -> 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 AttachPolicy where
  toHeaders :: AttachPolicy -> [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.AttachPolicy" ::
                          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 AttachPolicy where
  toJSON :: AttachPolicy -> Value
toJSON AttachPolicy' {Text
targetId :: Text
policyId :: Text
$sel:targetId:AttachPolicy' :: AttachPolicy -> Text
$sel:policyId:AttachPolicy' :: AttachPolicy -> 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 AttachPolicy where
  toPath :: AttachPolicy -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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