{-# 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.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 the specified policy to the specified principal (certificate or
-- other credential).
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions AttachPolicy>
-- action.
module Amazonka.IoT.AttachPolicy
  ( -- * Creating a Request
    AttachPolicy (..),
    newAttachPolicy,

    -- * Request Lenses
    attachPolicy_policyName,
    attachPolicy_target,

    -- * 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.IoT.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 name of the policy to attach.
    AttachPolicy -> Text
policyName :: Prelude.Text,
    -- | The
    -- <https://docs.aws.amazon.com/iot/latest/developerguide/security-iam.html identity>
    -- to which the policy is attached. For example, a thing group or a
    -- certificate.
    AttachPolicy -> Text
target :: 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:
--
-- 'policyName', 'attachPolicy_policyName' - The name of the policy to attach.
--
-- 'target', 'attachPolicy_target' - The
-- <https://docs.aws.amazon.com/iot/latest/developerguide/security-iam.html identity>
-- to which the policy is attached. For example, a thing group or a
-- certificate.
newAttachPolicy ::
  -- | 'policyName'
  Prelude.Text ->
  -- | 'target'
  Prelude.Text ->
  AttachPolicy
newAttachPolicy :: Text -> Text -> AttachPolicy
newAttachPolicy Text
pPolicyName_ Text
pTarget_ =
  AttachPolicy'
    { $sel:policyName:AttachPolicy' :: Text
policyName = Text
pPolicyName_,
      $sel:target:AttachPolicy' :: Text
target = Text
pTarget_
    }

-- | The name of the policy to attach.
attachPolicy_policyName :: Lens.Lens' AttachPolicy Prelude.Text
attachPolicy_policyName :: Lens' AttachPolicy Text
attachPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachPolicy' {Text
policyName :: Text
$sel:policyName:AttachPolicy' :: AttachPolicy -> Text
policyName} -> Text
policyName) (\s :: AttachPolicy
s@AttachPolicy' {} Text
a -> AttachPolicy
s {$sel:policyName:AttachPolicy' :: Text
policyName = Text
a} :: AttachPolicy)

-- | The
-- <https://docs.aws.amazon.com/iot/latest/developerguide/security-iam.html identity>
-- to which the policy is attached. For example, a thing group or a
-- certificate.
attachPolicy_target :: Lens.Lens' AttachPolicy Prelude.Text
attachPolicy_target :: Lens' AttachPolicy Text
attachPolicy_target = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachPolicy' {Text
target :: Text
$sel:target:AttachPolicy' :: AttachPolicy -> Text
target} -> Text
target) (\s :: AttachPolicy
s@AttachPolicy' {} Text
a -> AttachPolicy
s {$sel:target:AttachPolicy' :: Text
target = 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.putJSON (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
target :: Text
policyName :: Text
$sel:target:AttachPolicy' :: AttachPolicy -> Text
$sel:policyName:AttachPolicy' :: AttachPolicy -> 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 AttachPolicy where
  rnf :: AttachPolicy -> ()
rnf AttachPolicy' {Text
target :: Text
policyName :: Text
$sel:target:AttachPolicy' :: AttachPolicy -> Text
$sel:policyName:AttachPolicy' :: AttachPolicy -> 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 AttachPolicy where
  toHeaders :: AttachPolicy -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON AttachPolicy where
  toJSON :: AttachPolicy -> Value
toJSON AttachPolicy' {Text
target :: Text
policyName :: Text
$sel:target:AttachPolicy' :: AttachPolicy -> Text
$sel:policyName:AttachPolicy' :: AttachPolicy -> 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 AttachPolicy where
  toPath :: AttachPolicy -> ByteString
toPath AttachPolicy' {Text
target :: Text
policyName :: Text
$sel:target:AttachPolicy' :: AttachPolicy -> Text
$sel:policyName:AttachPolicy' :: AttachPolicy -> 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 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
_ = ()