{-# 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.Greengrass.AssociateRoleToGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates a role with a group. Your Greengrass core will use the role
-- to access AWS cloud services. The role\'s permissions should allow
-- Greengrass core Lambda functions to perform actions against the cloud.
module Amazonka.Greengrass.AssociateRoleToGroup
  ( -- * Creating a Request
    AssociateRoleToGroup (..),
    newAssociateRoleToGroup,

    -- * Request Lenses
    associateRoleToGroup_groupId,
    associateRoleToGroup_roleArn,

    -- * Destructuring the Response
    AssociateRoleToGroupResponse (..),
    newAssociateRoleToGroupResponse,

    -- * Response Lenses
    associateRoleToGroupResponse_associatedAt,
    associateRoleToGroupResponse_httpStatus,
  )
where

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

-- | /See:/ 'newAssociateRoleToGroup' smart constructor.
data AssociateRoleToGroup = AssociateRoleToGroup'
  { -- | The ID of the Greengrass group.
    AssociateRoleToGroup -> Text
groupId :: Prelude.Text,
    -- | The ARN of the role you wish to associate with this group. The existence
    -- of the role is not validated.
    AssociateRoleToGroup -> Text
roleArn :: Prelude.Text
  }
  deriving (AssociateRoleToGroup -> AssociateRoleToGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateRoleToGroup -> AssociateRoleToGroup -> Bool
$c/= :: AssociateRoleToGroup -> AssociateRoleToGroup -> Bool
== :: AssociateRoleToGroup -> AssociateRoleToGroup -> Bool
$c== :: AssociateRoleToGroup -> AssociateRoleToGroup -> Bool
Prelude.Eq, ReadPrec [AssociateRoleToGroup]
ReadPrec AssociateRoleToGroup
Int -> ReadS AssociateRoleToGroup
ReadS [AssociateRoleToGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateRoleToGroup]
$creadListPrec :: ReadPrec [AssociateRoleToGroup]
readPrec :: ReadPrec AssociateRoleToGroup
$creadPrec :: ReadPrec AssociateRoleToGroup
readList :: ReadS [AssociateRoleToGroup]
$creadList :: ReadS [AssociateRoleToGroup]
readsPrec :: Int -> ReadS AssociateRoleToGroup
$creadsPrec :: Int -> ReadS AssociateRoleToGroup
Prelude.Read, Int -> AssociateRoleToGroup -> ShowS
[AssociateRoleToGroup] -> ShowS
AssociateRoleToGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateRoleToGroup] -> ShowS
$cshowList :: [AssociateRoleToGroup] -> ShowS
show :: AssociateRoleToGroup -> String
$cshow :: AssociateRoleToGroup -> String
showsPrec :: Int -> AssociateRoleToGroup -> ShowS
$cshowsPrec :: Int -> AssociateRoleToGroup -> ShowS
Prelude.Show, forall x. Rep AssociateRoleToGroup x -> AssociateRoleToGroup
forall x. AssociateRoleToGroup -> Rep AssociateRoleToGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateRoleToGroup x -> AssociateRoleToGroup
$cfrom :: forall x. AssociateRoleToGroup -> Rep AssociateRoleToGroup x
Prelude.Generic)

-- |
-- Create a value of 'AssociateRoleToGroup' 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:
--
-- 'groupId', 'associateRoleToGroup_groupId' - The ID of the Greengrass group.
--
-- 'roleArn', 'associateRoleToGroup_roleArn' - The ARN of the role you wish to associate with this group. The existence
-- of the role is not validated.
newAssociateRoleToGroup ::
  -- | 'groupId'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  AssociateRoleToGroup
newAssociateRoleToGroup :: Text -> Text -> AssociateRoleToGroup
newAssociateRoleToGroup Text
pGroupId_ Text
pRoleArn_ =
  AssociateRoleToGroup'
    { $sel:groupId:AssociateRoleToGroup' :: Text
groupId = Text
pGroupId_,
      $sel:roleArn:AssociateRoleToGroup' :: Text
roleArn = Text
pRoleArn_
    }

-- | The ID of the Greengrass group.
associateRoleToGroup_groupId :: Lens.Lens' AssociateRoleToGroup Prelude.Text
associateRoleToGroup_groupId :: Lens' AssociateRoleToGroup Text
associateRoleToGroup_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateRoleToGroup' {Text
groupId :: Text
$sel:groupId:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
groupId} -> Text
groupId) (\s :: AssociateRoleToGroup
s@AssociateRoleToGroup' {} Text
a -> AssociateRoleToGroup
s {$sel:groupId:AssociateRoleToGroup' :: Text
groupId = Text
a} :: AssociateRoleToGroup)

-- | The ARN of the role you wish to associate with this group. The existence
-- of the role is not validated.
associateRoleToGroup_roleArn :: Lens.Lens' AssociateRoleToGroup Prelude.Text
associateRoleToGroup_roleArn :: Lens' AssociateRoleToGroup Text
associateRoleToGroup_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateRoleToGroup' {Text
roleArn :: Text
$sel:roleArn:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
roleArn} -> Text
roleArn) (\s :: AssociateRoleToGroup
s@AssociateRoleToGroup' {} Text
a -> AssociateRoleToGroup
s {$sel:roleArn:AssociateRoleToGroup' :: Text
roleArn = Text
a} :: AssociateRoleToGroup)

instance Core.AWSRequest AssociateRoleToGroup where
  type
    AWSResponse AssociateRoleToGroup =
      AssociateRoleToGroupResponse
  request :: (Service -> Service)
-> AssociateRoleToGroup -> Request AssociateRoleToGroup
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 AssociateRoleToGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateRoleToGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> AssociateRoleToGroupResponse
AssociateRoleToGroupResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"AssociatedAt")
            forall (f :: * -> *) a b. Applicative f => 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 AssociateRoleToGroup where
  hashWithSalt :: Int -> AssociateRoleToGroup -> Int
hashWithSalt Int
_salt AssociateRoleToGroup' {Text
roleArn :: Text
groupId :: Text
$sel:roleArn:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
$sel:groupId:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData AssociateRoleToGroup where
  rnf :: AssociateRoleToGroup -> ()
rnf AssociateRoleToGroup' {Text
roleArn :: Text
groupId :: Text
$sel:roleArn:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
$sel:groupId:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
groupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn

instance Data.ToHeaders AssociateRoleToGroup where
  toHeaders :: AssociateRoleToGroup -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

instance Data.ToPath AssociateRoleToGroup where
  toPath :: AssociateRoleToGroup -> ByteString
toPath AssociateRoleToGroup' {Text
roleArn :: Text
groupId :: Text
$sel:roleArn:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
$sel:groupId:AssociateRoleToGroup' :: AssociateRoleToGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/greengrass/groups/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
groupId, ByteString
"/role"]

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

-- | /See:/ 'newAssociateRoleToGroupResponse' smart constructor.
data AssociateRoleToGroupResponse = AssociateRoleToGroupResponse'
  { -- | The time, in milliseconds since the epoch, when the role ARN was
    -- associated with the group.
    AssociateRoleToGroupResponse -> Maybe Text
associatedAt :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    AssociateRoleToGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AssociateRoleToGroupResponse
-> AssociateRoleToGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateRoleToGroupResponse
-> AssociateRoleToGroupResponse -> Bool
$c/= :: AssociateRoleToGroupResponse
-> AssociateRoleToGroupResponse -> Bool
== :: AssociateRoleToGroupResponse
-> AssociateRoleToGroupResponse -> Bool
$c== :: AssociateRoleToGroupResponse
-> AssociateRoleToGroupResponse -> Bool
Prelude.Eq, ReadPrec [AssociateRoleToGroupResponse]
ReadPrec AssociateRoleToGroupResponse
Int -> ReadS AssociateRoleToGroupResponse
ReadS [AssociateRoleToGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateRoleToGroupResponse]
$creadListPrec :: ReadPrec [AssociateRoleToGroupResponse]
readPrec :: ReadPrec AssociateRoleToGroupResponse
$creadPrec :: ReadPrec AssociateRoleToGroupResponse
readList :: ReadS [AssociateRoleToGroupResponse]
$creadList :: ReadS [AssociateRoleToGroupResponse]
readsPrec :: Int -> ReadS AssociateRoleToGroupResponse
$creadsPrec :: Int -> ReadS AssociateRoleToGroupResponse
Prelude.Read, Int -> AssociateRoleToGroupResponse -> ShowS
[AssociateRoleToGroupResponse] -> ShowS
AssociateRoleToGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateRoleToGroupResponse] -> ShowS
$cshowList :: [AssociateRoleToGroupResponse] -> ShowS
show :: AssociateRoleToGroupResponse -> String
$cshow :: AssociateRoleToGroupResponse -> String
showsPrec :: Int -> AssociateRoleToGroupResponse -> ShowS
$cshowsPrec :: Int -> AssociateRoleToGroupResponse -> ShowS
Prelude.Show, forall x.
Rep AssociateRoleToGroupResponse x -> AssociateRoleToGroupResponse
forall x.
AssociateRoleToGroupResponse -> Rep AssociateRoleToGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateRoleToGroupResponse x -> AssociateRoleToGroupResponse
$cfrom :: forall x.
AssociateRoleToGroupResponse -> Rep AssociateRoleToGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'AssociateRoleToGroupResponse' 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:
--
-- 'associatedAt', 'associateRoleToGroupResponse_associatedAt' - The time, in milliseconds since the epoch, when the role ARN was
-- associated with the group.
--
-- 'httpStatus', 'associateRoleToGroupResponse_httpStatus' - The response's http status code.
newAssociateRoleToGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssociateRoleToGroupResponse
newAssociateRoleToGroupResponse :: Int -> AssociateRoleToGroupResponse
newAssociateRoleToGroupResponse Int
pHttpStatus_ =
  AssociateRoleToGroupResponse'
    { $sel:associatedAt:AssociateRoleToGroupResponse' :: Maybe Text
associatedAt =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssociateRoleToGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time, in milliseconds since the epoch, when the role ARN was
-- associated with the group.
associateRoleToGroupResponse_associatedAt :: Lens.Lens' AssociateRoleToGroupResponse (Prelude.Maybe Prelude.Text)
associateRoleToGroupResponse_associatedAt :: Lens' AssociateRoleToGroupResponse (Maybe Text)
associateRoleToGroupResponse_associatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateRoleToGroupResponse' {Maybe Text
associatedAt :: Maybe Text
$sel:associatedAt:AssociateRoleToGroupResponse' :: AssociateRoleToGroupResponse -> Maybe Text
associatedAt} -> Maybe Text
associatedAt) (\s :: AssociateRoleToGroupResponse
s@AssociateRoleToGroupResponse' {} Maybe Text
a -> AssociateRoleToGroupResponse
s {$sel:associatedAt:AssociateRoleToGroupResponse' :: Maybe Text
associatedAt = Maybe Text
a} :: AssociateRoleToGroupResponse)

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

instance Prelude.NFData AssociateRoleToGroupResponse where
  rnf :: AssociateRoleToGroupResponse -> ()
rnf AssociateRoleToGroupResponse' {Int
Maybe Text
httpStatus :: Int
associatedAt :: Maybe Text
$sel:httpStatus:AssociateRoleToGroupResponse' :: AssociateRoleToGroupResponse -> Int
$sel:associatedAt:AssociateRoleToGroupResponse' :: AssociateRoleToGroupResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
associatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus