{-# 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.EC2.AssociateIamInstanceProfile
-- 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 an IAM instance profile with a running or stopped instance.
-- You cannot associate more than one IAM instance profile with an
-- instance.
module Amazonka.EC2.AssociateIamInstanceProfile
  ( -- * Creating a Request
    AssociateIamInstanceProfile (..),
    newAssociateIamInstanceProfile,

    -- * Request Lenses
    associateIamInstanceProfile_iamInstanceProfile,
    associateIamInstanceProfile_instanceId,

    -- * Destructuring the Response
    AssociateIamInstanceProfileResponse (..),
    newAssociateIamInstanceProfileResponse,

    -- * Response Lenses
    associateIamInstanceProfileResponse_iamInstanceProfileAssociation,
    associateIamInstanceProfileResponse_httpStatus,
  )
where

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

-- | /See:/ 'newAssociateIamInstanceProfile' smart constructor.
data AssociateIamInstanceProfile = AssociateIamInstanceProfile'
  { -- | The IAM instance profile.
    AssociateIamInstanceProfile -> IamInstanceProfileSpecification
iamInstanceProfile :: IamInstanceProfileSpecification,
    -- | The ID of the instance.
    AssociateIamInstanceProfile -> Text
instanceId :: Prelude.Text
  }
  deriving (AssociateIamInstanceProfile -> AssociateIamInstanceProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateIamInstanceProfile -> AssociateIamInstanceProfile -> Bool
$c/= :: AssociateIamInstanceProfile -> AssociateIamInstanceProfile -> Bool
== :: AssociateIamInstanceProfile -> AssociateIamInstanceProfile -> Bool
$c== :: AssociateIamInstanceProfile -> AssociateIamInstanceProfile -> Bool
Prelude.Eq, ReadPrec [AssociateIamInstanceProfile]
ReadPrec AssociateIamInstanceProfile
Int -> ReadS AssociateIamInstanceProfile
ReadS [AssociateIamInstanceProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateIamInstanceProfile]
$creadListPrec :: ReadPrec [AssociateIamInstanceProfile]
readPrec :: ReadPrec AssociateIamInstanceProfile
$creadPrec :: ReadPrec AssociateIamInstanceProfile
readList :: ReadS [AssociateIamInstanceProfile]
$creadList :: ReadS [AssociateIamInstanceProfile]
readsPrec :: Int -> ReadS AssociateIamInstanceProfile
$creadsPrec :: Int -> ReadS AssociateIamInstanceProfile
Prelude.Read, Int -> AssociateIamInstanceProfile -> ShowS
[AssociateIamInstanceProfile] -> ShowS
AssociateIamInstanceProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateIamInstanceProfile] -> ShowS
$cshowList :: [AssociateIamInstanceProfile] -> ShowS
show :: AssociateIamInstanceProfile -> String
$cshow :: AssociateIamInstanceProfile -> String
showsPrec :: Int -> AssociateIamInstanceProfile -> ShowS
$cshowsPrec :: Int -> AssociateIamInstanceProfile -> ShowS
Prelude.Show, forall x.
Rep AssociateIamInstanceProfile x -> AssociateIamInstanceProfile
forall x.
AssociateIamInstanceProfile -> Rep AssociateIamInstanceProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateIamInstanceProfile x -> AssociateIamInstanceProfile
$cfrom :: forall x.
AssociateIamInstanceProfile -> Rep AssociateIamInstanceProfile x
Prelude.Generic)

-- |
-- Create a value of 'AssociateIamInstanceProfile' 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:
--
-- 'iamInstanceProfile', 'associateIamInstanceProfile_iamInstanceProfile' - The IAM instance profile.
--
-- 'instanceId', 'associateIamInstanceProfile_instanceId' - The ID of the instance.
newAssociateIamInstanceProfile ::
  -- | 'iamInstanceProfile'
  IamInstanceProfileSpecification ->
  -- | 'instanceId'
  Prelude.Text ->
  AssociateIamInstanceProfile
newAssociateIamInstanceProfile :: IamInstanceProfileSpecification
-> Text -> AssociateIamInstanceProfile
newAssociateIamInstanceProfile
  IamInstanceProfileSpecification
pIamInstanceProfile_
  Text
pInstanceId_ =
    AssociateIamInstanceProfile'
      { $sel:iamInstanceProfile:AssociateIamInstanceProfile' :: IamInstanceProfileSpecification
iamInstanceProfile =
          IamInstanceProfileSpecification
pIamInstanceProfile_,
        $sel:instanceId:AssociateIamInstanceProfile' :: Text
instanceId = Text
pInstanceId_
      }

-- | The IAM instance profile.
associateIamInstanceProfile_iamInstanceProfile :: Lens.Lens' AssociateIamInstanceProfile IamInstanceProfileSpecification
associateIamInstanceProfile_iamInstanceProfile :: Lens' AssociateIamInstanceProfile IamInstanceProfileSpecification
associateIamInstanceProfile_iamInstanceProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateIamInstanceProfile' {IamInstanceProfileSpecification
iamInstanceProfile :: IamInstanceProfileSpecification
$sel:iamInstanceProfile:AssociateIamInstanceProfile' :: AssociateIamInstanceProfile -> IamInstanceProfileSpecification
iamInstanceProfile} -> IamInstanceProfileSpecification
iamInstanceProfile) (\s :: AssociateIamInstanceProfile
s@AssociateIamInstanceProfile' {} IamInstanceProfileSpecification
a -> AssociateIamInstanceProfile
s {$sel:iamInstanceProfile:AssociateIamInstanceProfile' :: IamInstanceProfileSpecification
iamInstanceProfile = IamInstanceProfileSpecification
a} :: AssociateIamInstanceProfile)

-- | The ID of the instance.
associateIamInstanceProfile_instanceId :: Lens.Lens' AssociateIamInstanceProfile Prelude.Text
associateIamInstanceProfile_instanceId :: Lens' AssociateIamInstanceProfile Text
associateIamInstanceProfile_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateIamInstanceProfile' {Text
instanceId :: Text
$sel:instanceId:AssociateIamInstanceProfile' :: AssociateIamInstanceProfile -> Text
instanceId} -> Text
instanceId) (\s :: AssociateIamInstanceProfile
s@AssociateIamInstanceProfile' {} Text
a -> AssociateIamInstanceProfile
s {$sel:instanceId:AssociateIamInstanceProfile' :: Text
instanceId = Text
a} :: AssociateIamInstanceProfile)

instance Core.AWSRequest AssociateIamInstanceProfile where
  type
    AWSResponse AssociateIamInstanceProfile =
      AssociateIamInstanceProfileResponse
  request :: (Service -> Service)
-> AssociateIamInstanceProfile
-> Request AssociateIamInstanceProfile
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AssociateIamInstanceProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateIamInstanceProfile)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe IamInstanceProfileAssociation
-> Int -> AssociateIamInstanceProfileResponse
AssociateIamInstanceProfileResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"iamInstanceProfileAssociation")
            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 AssociateIamInstanceProfile where
  hashWithSalt :: Int -> AssociateIamInstanceProfile -> Int
hashWithSalt Int
_salt AssociateIamInstanceProfile' {Text
IamInstanceProfileSpecification
instanceId :: Text
iamInstanceProfile :: IamInstanceProfileSpecification
$sel:instanceId:AssociateIamInstanceProfile' :: AssociateIamInstanceProfile -> Text
$sel:iamInstanceProfile:AssociateIamInstanceProfile' :: AssociateIamInstanceProfile -> IamInstanceProfileSpecification
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IamInstanceProfileSpecification
iamInstanceProfile
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

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

instance Data.ToHeaders AssociateIamInstanceProfile where
  toHeaders :: AssociateIamInstanceProfile -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AssociateIamInstanceProfile where
  toQuery :: AssociateIamInstanceProfile -> QueryString
toQuery AssociateIamInstanceProfile' {Text
IamInstanceProfileSpecification
instanceId :: Text
iamInstanceProfile :: IamInstanceProfileSpecification
$sel:instanceId:AssociateIamInstanceProfile' :: AssociateIamInstanceProfile -> Text
$sel:iamInstanceProfile:AssociateIamInstanceProfile' :: AssociateIamInstanceProfile -> IamInstanceProfileSpecification
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"AssociateIamInstanceProfile" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"IamInstanceProfile" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: IamInstanceProfileSpecification
iamInstanceProfile,
        ByteString
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceId
      ]

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

-- |
-- Create a value of 'AssociateIamInstanceProfileResponse' 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:
--
-- 'iamInstanceProfileAssociation', 'associateIamInstanceProfileResponse_iamInstanceProfileAssociation' - Information about the IAM instance profile association.
--
-- 'httpStatus', 'associateIamInstanceProfileResponse_httpStatus' - The response's http status code.
newAssociateIamInstanceProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssociateIamInstanceProfileResponse
newAssociateIamInstanceProfileResponse :: Int -> AssociateIamInstanceProfileResponse
newAssociateIamInstanceProfileResponse Int
pHttpStatus_ =
  AssociateIamInstanceProfileResponse'
    { $sel:iamInstanceProfileAssociation:AssociateIamInstanceProfileResponse' :: Maybe IamInstanceProfileAssociation
iamInstanceProfileAssociation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssociateIamInstanceProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the IAM instance profile association.
associateIamInstanceProfileResponse_iamInstanceProfileAssociation :: Lens.Lens' AssociateIamInstanceProfileResponse (Prelude.Maybe IamInstanceProfileAssociation)
associateIamInstanceProfileResponse_iamInstanceProfileAssociation :: Lens'
  AssociateIamInstanceProfileResponse
  (Maybe IamInstanceProfileAssociation)
associateIamInstanceProfileResponse_iamInstanceProfileAssociation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateIamInstanceProfileResponse' {Maybe IamInstanceProfileAssociation
iamInstanceProfileAssociation :: Maybe IamInstanceProfileAssociation
$sel:iamInstanceProfileAssociation:AssociateIamInstanceProfileResponse' :: AssociateIamInstanceProfileResponse
-> Maybe IamInstanceProfileAssociation
iamInstanceProfileAssociation} -> Maybe IamInstanceProfileAssociation
iamInstanceProfileAssociation) (\s :: AssociateIamInstanceProfileResponse
s@AssociateIamInstanceProfileResponse' {} Maybe IamInstanceProfileAssociation
a -> AssociateIamInstanceProfileResponse
s {$sel:iamInstanceProfileAssociation:AssociateIamInstanceProfileResponse' :: Maybe IamInstanceProfileAssociation
iamInstanceProfileAssociation = Maybe IamInstanceProfileAssociation
a} :: AssociateIamInstanceProfileResponse)

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

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