{-# 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.ReplaceIamInstanceProfileAssociation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Replaces an IAM instance profile for the specified running instance. You
-- can use this action to change the IAM instance profile that\'s
-- associated with an instance without having to disassociate the existing
-- IAM instance profile first.
--
-- Use DescribeIamInstanceProfileAssociations to get the association ID.
module Amazonka.EC2.ReplaceIamInstanceProfileAssociation
  ( -- * Creating a Request
    ReplaceIamInstanceProfileAssociation (..),
    newReplaceIamInstanceProfileAssociation,

    -- * Request Lenses
    replaceIamInstanceProfileAssociation_iamInstanceProfile,
    replaceIamInstanceProfileAssociation_associationId,

    -- * Destructuring the Response
    ReplaceIamInstanceProfileAssociationResponse (..),
    newReplaceIamInstanceProfileAssociationResponse,

    -- * Response Lenses
    replaceIamInstanceProfileAssociationResponse_iamInstanceProfileAssociation,
    replaceIamInstanceProfileAssociationResponse_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:/ 'newReplaceIamInstanceProfileAssociation' smart constructor.
data ReplaceIamInstanceProfileAssociation = ReplaceIamInstanceProfileAssociation'
  { -- | The IAM instance profile.
    ReplaceIamInstanceProfileAssociation
-> IamInstanceProfileSpecification
iamInstanceProfile :: IamInstanceProfileSpecification,
    -- | The ID of the existing IAM instance profile association.
    ReplaceIamInstanceProfileAssociation -> Text
associationId :: Prelude.Text
  }
  deriving (ReplaceIamInstanceProfileAssociation
-> ReplaceIamInstanceProfileAssociation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplaceIamInstanceProfileAssociation
-> ReplaceIamInstanceProfileAssociation -> Bool
$c/= :: ReplaceIamInstanceProfileAssociation
-> ReplaceIamInstanceProfileAssociation -> Bool
== :: ReplaceIamInstanceProfileAssociation
-> ReplaceIamInstanceProfileAssociation -> Bool
$c== :: ReplaceIamInstanceProfileAssociation
-> ReplaceIamInstanceProfileAssociation -> Bool
Prelude.Eq, ReadPrec [ReplaceIamInstanceProfileAssociation]
ReadPrec ReplaceIamInstanceProfileAssociation
Int -> ReadS ReplaceIamInstanceProfileAssociation
ReadS [ReplaceIamInstanceProfileAssociation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReplaceIamInstanceProfileAssociation]
$creadListPrec :: ReadPrec [ReplaceIamInstanceProfileAssociation]
readPrec :: ReadPrec ReplaceIamInstanceProfileAssociation
$creadPrec :: ReadPrec ReplaceIamInstanceProfileAssociation
readList :: ReadS [ReplaceIamInstanceProfileAssociation]
$creadList :: ReadS [ReplaceIamInstanceProfileAssociation]
readsPrec :: Int -> ReadS ReplaceIamInstanceProfileAssociation
$creadsPrec :: Int -> ReadS ReplaceIamInstanceProfileAssociation
Prelude.Read, Int -> ReplaceIamInstanceProfileAssociation -> ShowS
[ReplaceIamInstanceProfileAssociation] -> ShowS
ReplaceIamInstanceProfileAssociation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplaceIamInstanceProfileAssociation] -> ShowS
$cshowList :: [ReplaceIamInstanceProfileAssociation] -> ShowS
show :: ReplaceIamInstanceProfileAssociation -> String
$cshow :: ReplaceIamInstanceProfileAssociation -> String
showsPrec :: Int -> ReplaceIamInstanceProfileAssociation -> ShowS
$cshowsPrec :: Int -> ReplaceIamInstanceProfileAssociation -> ShowS
Prelude.Show, forall x.
Rep ReplaceIamInstanceProfileAssociation x
-> ReplaceIamInstanceProfileAssociation
forall x.
ReplaceIamInstanceProfileAssociation
-> Rep ReplaceIamInstanceProfileAssociation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ReplaceIamInstanceProfileAssociation x
-> ReplaceIamInstanceProfileAssociation
$cfrom :: forall x.
ReplaceIamInstanceProfileAssociation
-> Rep ReplaceIamInstanceProfileAssociation x
Prelude.Generic)

-- |
-- Create a value of 'ReplaceIamInstanceProfileAssociation' 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', 'replaceIamInstanceProfileAssociation_iamInstanceProfile' - The IAM instance profile.
--
-- 'associationId', 'replaceIamInstanceProfileAssociation_associationId' - The ID of the existing IAM instance profile association.
newReplaceIamInstanceProfileAssociation ::
  -- | 'iamInstanceProfile'
  IamInstanceProfileSpecification ->
  -- | 'associationId'
  Prelude.Text ->
  ReplaceIamInstanceProfileAssociation
newReplaceIamInstanceProfileAssociation :: IamInstanceProfileSpecification
-> Text -> ReplaceIamInstanceProfileAssociation
newReplaceIamInstanceProfileAssociation
  IamInstanceProfileSpecification
pIamInstanceProfile_
  Text
pAssociationId_ =
    ReplaceIamInstanceProfileAssociation'
      { $sel:iamInstanceProfile:ReplaceIamInstanceProfileAssociation' :: IamInstanceProfileSpecification
iamInstanceProfile =
          IamInstanceProfileSpecification
pIamInstanceProfile_,
        $sel:associationId:ReplaceIamInstanceProfileAssociation' :: Text
associationId = Text
pAssociationId_
      }

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

-- | The ID of the existing IAM instance profile association.
replaceIamInstanceProfileAssociation_associationId :: Lens.Lens' ReplaceIamInstanceProfileAssociation Prelude.Text
replaceIamInstanceProfileAssociation_associationId :: Lens' ReplaceIamInstanceProfileAssociation Text
replaceIamInstanceProfileAssociation_associationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplaceIamInstanceProfileAssociation' {Text
associationId :: Text
$sel:associationId:ReplaceIamInstanceProfileAssociation' :: ReplaceIamInstanceProfileAssociation -> Text
associationId} -> Text
associationId) (\s :: ReplaceIamInstanceProfileAssociation
s@ReplaceIamInstanceProfileAssociation' {} Text
a -> ReplaceIamInstanceProfileAssociation
s {$sel:associationId:ReplaceIamInstanceProfileAssociation' :: Text
associationId = Text
a} :: ReplaceIamInstanceProfileAssociation)

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

instance
  Prelude.NFData
    ReplaceIamInstanceProfileAssociation
  where
  rnf :: ReplaceIamInstanceProfileAssociation -> ()
rnf ReplaceIamInstanceProfileAssociation' {Text
IamInstanceProfileSpecification
associationId :: Text
iamInstanceProfile :: IamInstanceProfileSpecification
$sel:associationId:ReplaceIamInstanceProfileAssociation' :: ReplaceIamInstanceProfileAssociation -> Text
$sel:iamInstanceProfile:ReplaceIamInstanceProfileAssociation' :: ReplaceIamInstanceProfileAssociation
-> 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
associationId

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

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

instance
  Data.ToQuery
    ReplaceIamInstanceProfileAssociation
  where
  toQuery :: ReplaceIamInstanceProfileAssociation -> QueryString
toQuery ReplaceIamInstanceProfileAssociation' {Text
IamInstanceProfileSpecification
associationId :: Text
iamInstanceProfile :: IamInstanceProfileSpecification
$sel:associationId:ReplaceIamInstanceProfileAssociation' :: ReplaceIamInstanceProfileAssociation -> Text
$sel:iamInstanceProfile:ReplaceIamInstanceProfileAssociation' :: ReplaceIamInstanceProfileAssociation
-> IamInstanceProfileSpecification
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"ReplaceIamInstanceProfileAssociation" ::
                      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
"AssociationId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
associationId
      ]

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

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

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

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

instance
  Prelude.NFData
    ReplaceIamInstanceProfileAssociationResponse
  where
  rnf :: ReplaceIamInstanceProfileAssociationResponse -> ()
rnf ReplaceIamInstanceProfileAssociationResponse' {Int
Maybe IamInstanceProfileAssociation
httpStatus :: Int
iamInstanceProfileAssociation :: Maybe IamInstanceProfileAssociation
$sel:httpStatus:ReplaceIamInstanceProfileAssociationResponse' :: ReplaceIamInstanceProfileAssociationResponse -> Int
$sel:iamInstanceProfileAssociation:ReplaceIamInstanceProfileAssociationResponse' :: ReplaceIamInstanceProfileAssociationResponse
-> 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