{-# 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.AttachThingPrincipal
-- 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 principal to the specified thing. A principal can
-- be X.509 certificates, Amazon Cognito identities or federated
-- identities.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions AttachThingPrincipal>
-- action.
module Amazonka.IoT.AttachThingPrincipal
  ( -- * Creating a Request
    AttachThingPrincipal (..),
    newAttachThingPrincipal,

    -- * Request Lenses
    attachThingPrincipal_thingName,
    attachThingPrincipal_principal,

    -- * Destructuring the Response
    AttachThingPrincipalResponse (..),
    newAttachThingPrincipalResponse,

    -- * Response Lenses
    attachThingPrincipalResponse_httpStatus,
  )
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

-- | The input for the AttachThingPrincipal operation.
--
-- /See:/ 'newAttachThingPrincipal' smart constructor.
data AttachThingPrincipal = AttachThingPrincipal'
  { -- | The name of the thing.
    AttachThingPrincipal -> Text
thingName :: Prelude.Text,
    -- | The principal, which can be a certificate ARN (as returned from the
    -- CreateCertificate operation) or an Amazon Cognito ID.
    AttachThingPrincipal -> Text
principal :: Prelude.Text
  }
  deriving (AttachThingPrincipal -> AttachThingPrincipal -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachThingPrincipal -> AttachThingPrincipal -> Bool
$c/= :: AttachThingPrincipal -> AttachThingPrincipal -> Bool
== :: AttachThingPrincipal -> AttachThingPrincipal -> Bool
$c== :: AttachThingPrincipal -> AttachThingPrincipal -> Bool
Prelude.Eq, ReadPrec [AttachThingPrincipal]
ReadPrec AttachThingPrincipal
Int -> ReadS AttachThingPrincipal
ReadS [AttachThingPrincipal]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachThingPrincipal]
$creadListPrec :: ReadPrec [AttachThingPrincipal]
readPrec :: ReadPrec AttachThingPrincipal
$creadPrec :: ReadPrec AttachThingPrincipal
readList :: ReadS [AttachThingPrincipal]
$creadList :: ReadS [AttachThingPrincipal]
readsPrec :: Int -> ReadS AttachThingPrincipal
$creadsPrec :: Int -> ReadS AttachThingPrincipal
Prelude.Read, Int -> AttachThingPrincipal -> ShowS
[AttachThingPrincipal] -> ShowS
AttachThingPrincipal -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachThingPrincipal] -> ShowS
$cshowList :: [AttachThingPrincipal] -> ShowS
show :: AttachThingPrincipal -> String
$cshow :: AttachThingPrincipal -> String
showsPrec :: Int -> AttachThingPrincipal -> ShowS
$cshowsPrec :: Int -> AttachThingPrincipal -> ShowS
Prelude.Show, forall x. Rep AttachThingPrincipal x -> AttachThingPrincipal
forall x. AttachThingPrincipal -> Rep AttachThingPrincipal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachThingPrincipal x -> AttachThingPrincipal
$cfrom :: forall x. AttachThingPrincipal -> Rep AttachThingPrincipal x
Prelude.Generic)

-- |
-- Create a value of 'AttachThingPrincipal' 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:
--
-- 'thingName', 'attachThingPrincipal_thingName' - The name of the thing.
--
-- 'principal', 'attachThingPrincipal_principal' - The principal, which can be a certificate ARN (as returned from the
-- CreateCertificate operation) or an Amazon Cognito ID.
newAttachThingPrincipal ::
  -- | 'thingName'
  Prelude.Text ->
  -- | 'principal'
  Prelude.Text ->
  AttachThingPrincipal
newAttachThingPrincipal :: Text -> Text -> AttachThingPrincipal
newAttachThingPrincipal Text
pThingName_ Text
pPrincipal_ =
  AttachThingPrincipal'
    { $sel:thingName:AttachThingPrincipal' :: Text
thingName = Text
pThingName_,
      $sel:principal:AttachThingPrincipal' :: Text
principal = Text
pPrincipal_
    }

-- | The name of the thing.
attachThingPrincipal_thingName :: Lens.Lens' AttachThingPrincipal Prelude.Text
attachThingPrincipal_thingName :: Lens' AttachThingPrincipal Text
attachThingPrincipal_thingName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachThingPrincipal' {Text
thingName :: Text
$sel:thingName:AttachThingPrincipal' :: AttachThingPrincipal -> Text
thingName} -> Text
thingName) (\s :: AttachThingPrincipal
s@AttachThingPrincipal' {} Text
a -> AttachThingPrincipal
s {$sel:thingName:AttachThingPrincipal' :: Text
thingName = Text
a} :: AttachThingPrincipal)

-- | The principal, which can be a certificate ARN (as returned from the
-- CreateCertificate operation) or an Amazon Cognito ID.
attachThingPrincipal_principal :: Lens.Lens' AttachThingPrincipal Prelude.Text
attachThingPrincipal_principal :: Lens' AttachThingPrincipal Text
attachThingPrincipal_principal = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachThingPrincipal' {Text
principal :: Text
$sel:principal:AttachThingPrincipal' :: AttachThingPrincipal -> Text
principal} -> Text
principal) (\s :: AttachThingPrincipal
s@AttachThingPrincipal' {} Text
a -> AttachThingPrincipal
s {$sel:principal:AttachThingPrincipal' :: Text
principal = Text
a} :: AttachThingPrincipal)

instance Core.AWSRequest AttachThingPrincipal where
  type
    AWSResponse AttachThingPrincipal =
      AttachThingPrincipalResponse
  request :: (Service -> Service)
-> AttachThingPrincipal -> Request AttachThingPrincipal
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 AttachThingPrincipal
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AttachThingPrincipal)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> AttachThingPrincipalResponse
AttachThingPrincipalResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable AttachThingPrincipal where
  hashWithSalt :: Int -> AttachThingPrincipal -> Int
hashWithSalt Int
_salt AttachThingPrincipal' {Text
principal :: Text
thingName :: Text
$sel:principal:AttachThingPrincipal' :: AttachThingPrincipal -> Text
$sel:thingName:AttachThingPrincipal' :: AttachThingPrincipal -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
principal

instance Prelude.NFData AttachThingPrincipal where
  rnf :: AttachThingPrincipal -> ()
rnf AttachThingPrincipal' {Text
principal :: Text
thingName :: Text
$sel:principal:AttachThingPrincipal' :: AttachThingPrincipal -> Text
$sel:thingName:AttachThingPrincipal' :: AttachThingPrincipal -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
thingName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
principal

instance Data.ToHeaders AttachThingPrincipal where
  toHeaders :: AttachThingPrincipal -> ResponseHeaders
toHeaders AttachThingPrincipal' {Text
principal :: Text
thingName :: Text
$sel:principal:AttachThingPrincipal' :: AttachThingPrincipal -> Text
$sel:thingName:AttachThingPrincipal' :: AttachThingPrincipal -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [HeaderName
"x-amzn-principal" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
principal]

instance Data.ToJSON AttachThingPrincipal where
  toJSON :: AttachThingPrincipal -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath AttachThingPrincipal where
  toPath :: AttachThingPrincipal -> ByteString
toPath AttachThingPrincipal' {Text
principal :: Text
thingName :: Text
$sel:principal:AttachThingPrincipal' :: AttachThingPrincipal -> Text
$sel:thingName:AttachThingPrincipal' :: AttachThingPrincipal -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/things/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
thingName, ByteString
"/principals"]

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

-- | The output from the AttachThingPrincipal operation.
--
-- /See:/ 'newAttachThingPrincipalResponse' smart constructor.
data AttachThingPrincipalResponse = AttachThingPrincipalResponse'
  { -- | The response's http status code.
    AttachThingPrincipalResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AttachThingPrincipalResponse
-> AttachThingPrincipalResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachThingPrincipalResponse
-> AttachThingPrincipalResponse -> Bool
$c/= :: AttachThingPrincipalResponse
-> AttachThingPrincipalResponse -> Bool
== :: AttachThingPrincipalResponse
-> AttachThingPrincipalResponse -> Bool
$c== :: AttachThingPrincipalResponse
-> AttachThingPrincipalResponse -> Bool
Prelude.Eq, ReadPrec [AttachThingPrincipalResponse]
ReadPrec AttachThingPrincipalResponse
Int -> ReadS AttachThingPrincipalResponse
ReadS [AttachThingPrincipalResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachThingPrincipalResponse]
$creadListPrec :: ReadPrec [AttachThingPrincipalResponse]
readPrec :: ReadPrec AttachThingPrincipalResponse
$creadPrec :: ReadPrec AttachThingPrincipalResponse
readList :: ReadS [AttachThingPrincipalResponse]
$creadList :: ReadS [AttachThingPrincipalResponse]
readsPrec :: Int -> ReadS AttachThingPrincipalResponse
$creadsPrec :: Int -> ReadS AttachThingPrincipalResponse
Prelude.Read, Int -> AttachThingPrincipalResponse -> ShowS
[AttachThingPrincipalResponse] -> ShowS
AttachThingPrincipalResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachThingPrincipalResponse] -> ShowS
$cshowList :: [AttachThingPrincipalResponse] -> ShowS
show :: AttachThingPrincipalResponse -> String
$cshow :: AttachThingPrincipalResponse -> String
showsPrec :: Int -> AttachThingPrincipalResponse -> ShowS
$cshowsPrec :: Int -> AttachThingPrincipalResponse -> ShowS
Prelude.Show, forall x.
Rep AttachThingPrincipalResponse x -> AttachThingPrincipalResponse
forall x.
AttachThingPrincipalResponse -> Rep AttachThingPrincipalResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachThingPrincipalResponse x -> AttachThingPrincipalResponse
$cfrom :: forall x.
AttachThingPrincipalResponse -> Rep AttachThingPrincipalResponse x
Prelude.Generic)

-- |
-- Create a value of 'AttachThingPrincipalResponse' 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:
--
-- 'httpStatus', 'attachThingPrincipalResponse_httpStatus' - The response's http status code.
newAttachThingPrincipalResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AttachThingPrincipalResponse
newAttachThingPrincipalResponse :: Int -> AttachThingPrincipalResponse
newAttachThingPrincipalResponse Int
pHttpStatus_ =
  AttachThingPrincipalResponse'
    { $sel:httpStatus:AttachThingPrincipalResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

-- | The response's http status code.
attachThingPrincipalResponse_httpStatus :: Lens.Lens' AttachThingPrincipalResponse Prelude.Int
attachThingPrincipalResponse_httpStatus :: Lens' AttachThingPrincipalResponse Int
attachThingPrincipalResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachThingPrincipalResponse' {Int
httpStatus :: Int
$sel:httpStatus:AttachThingPrincipalResponse' :: AttachThingPrincipalResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AttachThingPrincipalResponse
s@AttachThingPrincipalResponse' {} Int
a -> AttachThingPrincipalResponse
s {$sel:httpStatus:AttachThingPrincipalResponse' :: Int
httpStatus = Int
a} :: AttachThingPrincipalResponse)

instance Prelude.NFData AttachThingPrincipalResponse where
  rnf :: AttachThingPrincipalResponse -> ()
rnf AttachThingPrincipalResponse' {Int
httpStatus :: Int
$sel:httpStatus:AttachThingPrincipalResponse' :: AttachThingPrincipalResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus