{-# 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.GetAssociatedRole
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the role associated with a particular group.
module Amazonka.Greengrass.GetAssociatedRole
  ( -- * Creating a Request
    GetAssociatedRole (..),
    newGetAssociatedRole,

    -- * Request Lenses
    getAssociatedRole_groupId,

    -- * Destructuring the Response
    GetAssociatedRoleResponse (..),
    newGetAssociatedRoleResponse,

    -- * Response Lenses
    getAssociatedRoleResponse_associatedAt,
    getAssociatedRoleResponse_roleArn,
    getAssociatedRoleResponse_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:/ 'newGetAssociatedRole' smart constructor.
data GetAssociatedRole = GetAssociatedRole'
  { -- | The ID of the Greengrass group.
    GetAssociatedRole -> Text
groupId :: Prelude.Text
  }
  deriving (GetAssociatedRole -> GetAssociatedRole -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAssociatedRole -> GetAssociatedRole -> Bool
$c/= :: GetAssociatedRole -> GetAssociatedRole -> Bool
== :: GetAssociatedRole -> GetAssociatedRole -> Bool
$c== :: GetAssociatedRole -> GetAssociatedRole -> Bool
Prelude.Eq, ReadPrec [GetAssociatedRole]
ReadPrec GetAssociatedRole
Int -> ReadS GetAssociatedRole
ReadS [GetAssociatedRole]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAssociatedRole]
$creadListPrec :: ReadPrec [GetAssociatedRole]
readPrec :: ReadPrec GetAssociatedRole
$creadPrec :: ReadPrec GetAssociatedRole
readList :: ReadS [GetAssociatedRole]
$creadList :: ReadS [GetAssociatedRole]
readsPrec :: Int -> ReadS GetAssociatedRole
$creadsPrec :: Int -> ReadS GetAssociatedRole
Prelude.Read, Int -> GetAssociatedRole -> ShowS
[GetAssociatedRole] -> ShowS
GetAssociatedRole -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAssociatedRole] -> ShowS
$cshowList :: [GetAssociatedRole] -> ShowS
show :: GetAssociatedRole -> String
$cshow :: GetAssociatedRole -> String
showsPrec :: Int -> GetAssociatedRole -> ShowS
$cshowsPrec :: Int -> GetAssociatedRole -> ShowS
Prelude.Show, forall x. Rep GetAssociatedRole x -> GetAssociatedRole
forall x. GetAssociatedRole -> Rep GetAssociatedRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAssociatedRole x -> GetAssociatedRole
$cfrom :: forall x. GetAssociatedRole -> Rep GetAssociatedRole x
Prelude.Generic)

-- |
-- Create a value of 'GetAssociatedRole' 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', 'getAssociatedRole_groupId' - The ID of the Greengrass group.
newGetAssociatedRole ::
  -- | 'groupId'
  Prelude.Text ->
  GetAssociatedRole
newGetAssociatedRole :: Text -> GetAssociatedRole
newGetAssociatedRole Text
pGroupId_ =
  GetAssociatedRole' {$sel:groupId:GetAssociatedRole' :: Text
groupId = Text
pGroupId_}

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

instance Core.AWSRequest GetAssociatedRole where
  type
    AWSResponse GetAssociatedRole =
      GetAssociatedRoleResponse
  request :: (Service -> Service)
-> GetAssociatedRole -> Request GetAssociatedRole
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetAssociatedRole
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAssociatedRole)))
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 -> Maybe Text -> Int -> GetAssociatedRoleResponse
GetAssociatedRoleResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoleArn")
            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 GetAssociatedRole where
  hashWithSalt :: Int -> GetAssociatedRole -> Int
hashWithSalt Int
_salt GetAssociatedRole' {Text
groupId :: Text
$sel:groupId:GetAssociatedRole' :: GetAssociatedRole -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId

instance Prelude.NFData GetAssociatedRole where
  rnf :: GetAssociatedRole -> ()
rnf GetAssociatedRole' {Text
groupId :: Text
$sel:groupId:GetAssociatedRole' :: GetAssociatedRole -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
groupId

instance Data.ToHeaders GetAssociatedRole where
  toHeaders :: GetAssociatedRole -> 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.ToPath GetAssociatedRole where
  toPath :: GetAssociatedRole -> ByteString
toPath GetAssociatedRole' {Text
groupId :: Text
$sel:groupId:GetAssociatedRole' :: GetAssociatedRole -> 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 GetAssociatedRole where
  toQuery :: GetAssociatedRole -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

-- |
-- Create a value of 'GetAssociatedRoleResponse' 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', 'getAssociatedRoleResponse_associatedAt' - The time when the role was associated with the group.
--
-- 'roleArn', 'getAssociatedRoleResponse_roleArn' - The ARN of the role that is associated with the group.
--
-- 'httpStatus', 'getAssociatedRoleResponse_httpStatus' - The response's http status code.
newGetAssociatedRoleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAssociatedRoleResponse
newGetAssociatedRoleResponse :: Int -> GetAssociatedRoleResponse
newGetAssociatedRoleResponse Int
pHttpStatus_ =
  GetAssociatedRoleResponse'
    { $sel:associatedAt:GetAssociatedRoleResponse' :: Maybe Text
associatedAt =
        forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:GetAssociatedRoleResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAssociatedRoleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time when the role was associated with the group.
getAssociatedRoleResponse_associatedAt :: Lens.Lens' GetAssociatedRoleResponse (Prelude.Maybe Prelude.Text)
getAssociatedRoleResponse_associatedAt :: Lens' GetAssociatedRoleResponse (Maybe Text)
getAssociatedRoleResponse_associatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssociatedRoleResponse' {Maybe Text
associatedAt :: Maybe Text
$sel:associatedAt:GetAssociatedRoleResponse' :: GetAssociatedRoleResponse -> Maybe Text
associatedAt} -> Maybe Text
associatedAt) (\s :: GetAssociatedRoleResponse
s@GetAssociatedRoleResponse' {} Maybe Text
a -> GetAssociatedRoleResponse
s {$sel:associatedAt:GetAssociatedRoleResponse' :: Maybe Text
associatedAt = Maybe Text
a} :: GetAssociatedRoleResponse)

-- | The ARN of the role that is associated with the group.
getAssociatedRoleResponse_roleArn :: Lens.Lens' GetAssociatedRoleResponse (Prelude.Maybe Prelude.Text)
getAssociatedRoleResponse_roleArn :: Lens' GetAssociatedRoleResponse (Maybe Text)
getAssociatedRoleResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssociatedRoleResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:GetAssociatedRoleResponse' :: GetAssociatedRoleResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: GetAssociatedRoleResponse
s@GetAssociatedRoleResponse' {} Maybe Text
a -> GetAssociatedRoleResponse
s {$sel:roleArn:GetAssociatedRoleResponse' :: Maybe Text
roleArn = Maybe Text
a} :: GetAssociatedRoleResponse)

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

instance Prelude.NFData GetAssociatedRoleResponse where
  rnf :: GetAssociatedRoleResponse -> ()
rnf GetAssociatedRoleResponse' {Int
Maybe Text
httpStatus :: Int
roleArn :: Maybe Text
associatedAt :: Maybe Text
$sel:httpStatus:GetAssociatedRoleResponse' :: GetAssociatedRoleResponse -> Int
$sel:roleArn:GetAssociatedRoleResponse' :: GetAssociatedRoleResponse -> Maybe Text
$sel:associatedAt:GetAssociatedRoleResponse' :: GetAssociatedRoleResponse -> 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 Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus