{-# 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.SSM.UpdateManagedInstanceRole
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Changes the Identity and Access Management (IAM) role that is assigned
-- to the on-premises server, edge device, or virtual machines (VM). IAM
-- roles are first assigned to these hybrid nodes during the activation
-- process. For more information, see CreateActivation.
module Amazonka.SSM.UpdateManagedInstanceRole
  ( -- * Creating a Request
    UpdateManagedInstanceRole (..),
    newUpdateManagedInstanceRole,

    -- * Request Lenses
    updateManagedInstanceRole_instanceId,
    updateManagedInstanceRole_iamRole,

    -- * Destructuring the Response
    UpdateManagedInstanceRoleResponse (..),
    newUpdateManagedInstanceRoleResponse,

    -- * Response Lenses
    updateManagedInstanceRoleResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateManagedInstanceRole' smart constructor.
data UpdateManagedInstanceRole = UpdateManagedInstanceRole'
  { -- | The ID of the managed node where you want to update the role.
    UpdateManagedInstanceRole -> Text
instanceId :: Prelude.Text,
    -- | The name of the Identity and Access Management (IAM) role that you want
    -- to assign to the managed node. This IAM role must provide AssumeRole
    -- permissions for the Amazon Web Services Systems Manager service
    -- principal @ssm.amazonaws.com@. For more information, see
    -- <https://docs.aws.amazon.com/systems-manager/latest/userguide/sysman-service-role.html Create an IAM service role for a hybrid environment>
    -- in the /Amazon Web Services Systems Manager User Guide/.
    --
    -- You can\'t specify an IAM service-linked role for this parameter. You
    -- must create a unique role.
    UpdateManagedInstanceRole -> Text
iamRole :: Prelude.Text
  }
  deriving (UpdateManagedInstanceRole -> UpdateManagedInstanceRole -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateManagedInstanceRole -> UpdateManagedInstanceRole -> Bool
$c/= :: UpdateManagedInstanceRole -> UpdateManagedInstanceRole -> Bool
== :: UpdateManagedInstanceRole -> UpdateManagedInstanceRole -> Bool
$c== :: UpdateManagedInstanceRole -> UpdateManagedInstanceRole -> Bool
Prelude.Eq, ReadPrec [UpdateManagedInstanceRole]
ReadPrec UpdateManagedInstanceRole
Int -> ReadS UpdateManagedInstanceRole
ReadS [UpdateManagedInstanceRole]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateManagedInstanceRole]
$creadListPrec :: ReadPrec [UpdateManagedInstanceRole]
readPrec :: ReadPrec UpdateManagedInstanceRole
$creadPrec :: ReadPrec UpdateManagedInstanceRole
readList :: ReadS [UpdateManagedInstanceRole]
$creadList :: ReadS [UpdateManagedInstanceRole]
readsPrec :: Int -> ReadS UpdateManagedInstanceRole
$creadsPrec :: Int -> ReadS UpdateManagedInstanceRole
Prelude.Read, Int -> UpdateManagedInstanceRole -> ShowS
[UpdateManagedInstanceRole] -> ShowS
UpdateManagedInstanceRole -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateManagedInstanceRole] -> ShowS
$cshowList :: [UpdateManagedInstanceRole] -> ShowS
show :: UpdateManagedInstanceRole -> String
$cshow :: UpdateManagedInstanceRole -> String
showsPrec :: Int -> UpdateManagedInstanceRole -> ShowS
$cshowsPrec :: Int -> UpdateManagedInstanceRole -> ShowS
Prelude.Show, forall x.
Rep UpdateManagedInstanceRole x -> UpdateManagedInstanceRole
forall x.
UpdateManagedInstanceRole -> Rep UpdateManagedInstanceRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateManagedInstanceRole x -> UpdateManagedInstanceRole
$cfrom :: forall x.
UpdateManagedInstanceRole -> Rep UpdateManagedInstanceRole x
Prelude.Generic)

-- |
-- Create a value of 'UpdateManagedInstanceRole' 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:
--
-- 'instanceId', 'updateManagedInstanceRole_instanceId' - The ID of the managed node where you want to update the role.
--
-- 'iamRole', 'updateManagedInstanceRole_iamRole' - The name of the Identity and Access Management (IAM) role that you want
-- to assign to the managed node. This IAM role must provide AssumeRole
-- permissions for the Amazon Web Services Systems Manager service
-- principal @ssm.amazonaws.com@. For more information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/sysman-service-role.html Create an IAM service role for a hybrid environment>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- You can\'t specify an IAM service-linked role for this parameter. You
-- must create a unique role.
newUpdateManagedInstanceRole ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'iamRole'
  Prelude.Text ->
  UpdateManagedInstanceRole
newUpdateManagedInstanceRole :: Text -> Text -> UpdateManagedInstanceRole
newUpdateManagedInstanceRole Text
pInstanceId_ Text
pIamRole_ =
  UpdateManagedInstanceRole'
    { $sel:instanceId:UpdateManagedInstanceRole' :: Text
instanceId =
        Text
pInstanceId_,
      $sel:iamRole:UpdateManagedInstanceRole' :: Text
iamRole = Text
pIamRole_
    }

-- | The ID of the managed node where you want to update the role.
updateManagedInstanceRole_instanceId :: Lens.Lens' UpdateManagedInstanceRole Prelude.Text
updateManagedInstanceRole_instanceId :: Lens' UpdateManagedInstanceRole Text
updateManagedInstanceRole_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateManagedInstanceRole' {Text
instanceId :: Text
$sel:instanceId:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
instanceId} -> Text
instanceId) (\s :: UpdateManagedInstanceRole
s@UpdateManagedInstanceRole' {} Text
a -> UpdateManagedInstanceRole
s {$sel:instanceId:UpdateManagedInstanceRole' :: Text
instanceId = Text
a} :: UpdateManagedInstanceRole)

-- | The name of the Identity and Access Management (IAM) role that you want
-- to assign to the managed node. This IAM role must provide AssumeRole
-- permissions for the Amazon Web Services Systems Manager service
-- principal @ssm.amazonaws.com@. For more information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/sysman-service-role.html Create an IAM service role for a hybrid environment>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- You can\'t specify an IAM service-linked role for this parameter. You
-- must create a unique role.
updateManagedInstanceRole_iamRole :: Lens.Lens' UpdateManagedInstanceRole Prelude.Text
updateManagedInstanceRole_iamRole :: Lens' UpdateManagedInstanceRole Text
updateManagedInstanceRole_iamRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateManagedInstanceRole' {Text
iamRole :: Text
$sel:iamRole:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
iamRole} -> Text
iamRole) (\s :: UpdateManagedInstanceRole
s@UpdateManagedInstanceRole' {} Text
a -> UpdateManagedInstanceRole
s {$sel:iamRole:UpdateManagedInstanceRole' :: Text
iamRole = Text
a} :: UpdateManagedInstanceRole)

instance Core.AWSRequest UpdateManagedInstanceRole where
  type
    AWSResponse UpdateManagedInstanceRole =
      UpdateManagedInstanceRoleResponse
  request :: (Service -> Service)
-> UpdateManagedInstanceRole -> Request UpdateManagedInstanceRole
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 UpdateManagedInstanceRole
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateManagedInstanceRole)))
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 -> UpdateManagedInstanceRoleResponse
UpdateManagedInstanceRoleResponse'
            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 UpdateManagedInstanceRole where
  hashWithSalt :: Int -> UpdateManagedInstanceRole -> Int
hashWithSalt Int
_salt UpdateManagedInstanceRole' {Text
iamRole :: Text
instanceId :: Text
$sel:iamRole:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
$sel:instanceId:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
iamRole

instance Prelude.NFData UpdateManagedInstanceRole where
  rnf :: UpdateManagedInstanceRole -> ()
rnf UpdateManagedInstanceRole' {Text
iamRole :: Text
instanceId :: Text
$sel:iamRole:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
$sel:instanceId:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
iamRole

instance Data.ToHeaders UpdateManagedInstanceRole where
  toHeaders :: UpdateManagedInstanceRole -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"AmazonSSM.UpdateManagedInstanceRole" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateManagedInstanceRole where
  toJSON :: UpdateManagedInstanceRole -> Value
toJSON UpdateManagedInstanceRole' {Text
iamRole :: Text
instanceId :: Text
$sel:iamRole:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
$sel:instanceId:UpdateManagedInstanceRole' :: UpdateManagedInstanceRole -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"InstanceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
instanceId),
            forall a. a -> Maybe a
Prelude.Just (Key
"IamRole" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
iamRole)
          ]
      )

instance Data.ToPath UpdateManagedInstanceRole where
  toPath :: UpdateManagedInstanceRole -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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