{-# 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.Inspector2.AssociateMember
-- 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 Amazon Web Services account with an Amazon Inspector
-- delegated administrator.
module Amazonka.Inspector2.AssociateMember
  ( -- * Creating a Request
    AssociateMember (..),
    newAssociateMember,

    -- * Request Lenses
    associateMember_accountId,

    -- * Destructuring the Response
    AssociateMemberResponse (..),
    newAssociateMemberResponse,

    -- * Response Lenses
    associateMemberResponse_httpStatus,
    associateMemberResponse_accountId,
  )
where

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

-- | /See:/ 'newAssociateMember' smart constructor.
data AssociateMember = AssociateMember'
  { -- | The Amazon Web Services account ID of the member account to be
    -- associated.
    AssociateMember -> Text
accountId :: Prelude.Text
  }
  deriving (AssociateMember -> AssociateMember -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateMember -> AssociateMember -> Bool
$c/= :: AssociateMember -> AssociateMember -> Bool
== :: AssociateMember -> AssociateMember -> Bool
$c== :: AssociateMember -> AssociateMember -> Bool
Prelude.Eq, ReadPrec [AssociateMember]
ReadPrec AssociateMember
Int -> ReadS AssociateMember
ReadS [AssociateMember]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateMember]
$creadListPrec :: ReadPrec [AssociateMember]
readPrec :: ReadPrec AssociateMember
$creadPrec :: ReadPrec AssociateMember
readList :: ReadS [AssociateMember]
$creadList :: ReadS [AssociateMember]
readsPrec :: Int -> ReadS AssociateMember
$creadsPrec :: Int -> ReadS AssociateMember
Prelude.Read, Int -> AssociateMember -> ShowS
[AssociateMember] -> ShowS
AssociateMember -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateMember] -> ShowS
$cshowList :: [AssociateMember] -> ShowS
show :: AssociateMember -> String
$cshow :: AssociateMember -> String
showsPrec :: Int -> AssociateMember -> ShowS
$cshowsPrec :: Int -> AssociateMember -> ShowS
Prelude.Show, forall x. Rep AssociateMember x -> AssociateMember
forall x. AssociateMember -> Rep AssociateMember x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateMember x -> AssociateMember
$cfrom :: forall x. AssociateMember -> Rep AssociateMember x
Prelude.Generic)

-- |
-- Create a value of 'AssociateMember' 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:
--
-- 'accountId', 'associateMember_accountId' - The Amazon Web Services account ID of the member account to be
-- associated.
newAssociateMember ::
  -- | 'accountId'
  Prelude.Text ->
  AssociateMember
newAssociateMember :: Text -> AssociateMember
newAssociateMember Text
pAccountId_ =
  AssociateMember' {$sel:accountId:AssociateMember' :: Text
accountId = Text
pAccountId_}

-- | The Amazon Web Services account ID of the member account to be
-- associated.
associateMember_accountId :: Lens.Lens' AssociateMember Prelude.Text
associateMember_accountId :: Lens' AssociateMember Text
associateMember_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMember' {Text
accountId :: Text
$sel:accountId:AssociateMember' :: AssociateMember -> Text
accountId} -> Text
accountId) (\s :: AssociateMember
s@AssociateMember' {} Text
a -> AssociateMember
s {$sel:accountId:AssociateMember' :: Text
accountId = Text
a} :: AssociateMember)

instance Core.AWSRequest AssociateMember where
  type
    AWSResponse AssociateMember =
      AssociateMemberResponse
  request :: (Service -> Service) -> AssociateMember -> Request AssociateMember
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 AssociateMember
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AssociateMember)))
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 ->
          Int -> Text -> AssociateMemberResponse
AssociateMemberResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"accountId")
      )

instance Prelude.Hashable AssociateMember where
  hashWithSalt :: Int -> AssociateMember -> Int
hashWithSalt Int
_salt AssociateMember' {Text
accountId :: Text
$sel:accountId:AssociateMember' :: AssociateMember -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId

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

instance Data.ToHeaders AssociateMember where
  toHeaders :: AssociateMember -> 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 AssociateMember where
  toJSON :: AssociateMember -> Value
toJSON AssociateMember' {Text
accountId :: Text
$sel:accountId:AssociateMember' :: AssociateMember -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"accountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
accountId)]
      )

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

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

-- | /See:/ 'newAssociateMemberResponse' smart constructor.
data AssociateMemberResponse = AssociateMemberResponse'
  { -- | The response's http status code.
    AssociateMemberResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Web Services account ID of the successfully associated member
    -- account.
    AssociateMemberResponse -> Text
accountId :: Prelude.Text
  }
  deriving (AssociateMemberResponse -> AssociateMemberResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateMemberResponse -> AssociateMemberResponse -> Bool
$c/= :: AssociateMemberResponse -> AssociateMemberResponse -> Bool
== :: AssociateMemberResponse -> AssociateMemberResponse -> Bool
$c== :: AssociateMemberResponse -> AssociateMemberResponse -> Bool
Prelude.Eq, ReadPrec [AssociateMemberResponse]
ReadPrec AssociateMemberResponse
Int -> ReadS AssociateMemberResponse
ReadS [AssociateMemberResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateMemberResponse]
$creadListPrec :: ReadPrec [AssociateMemberResponse]
readPrec :: ReadPrec AssociateMemberResponse
$creadPrec :: ReadPrec AssociateMemberResponse
readList :: ReadS [AssociateMemberResponse]
$creadList :: ReadS [AssociateMemberResponse]
readsPrec :: Int -> ReadS AssociateMemberResponse
$creadsPrec :: Int -> ReadS AssociateMemberResponse
Prelude.Read, Int -> AssociateMemberResponse -> ShowS
[AssociateMemberResponse] -> ShowS
AssociateMemberResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateMemberResponse] -> ShowS
$cshowList :: [AssociateMemberResponse] -> ShowS
show :: AssociateMemberResponse -> String
$cshow :: AssociateMemberResponse -> String
showsPrec :: Int -> AssociateMemberResponse -> ShowS
$cshowsPrec :: Int -> AssociateMemberResponse -> ShowS
Prelude.Show, forall x. Rep AssociateMemberResponse x -> AssociateMemberResponse
forall x. AssociateMemberResponse -> Rep AssociateMemberResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateMemberResponse x -> AssociateMemberResponse
$cfrom :: forall x. AssociateMemberResponse -> Rep AssociateMemberResponse x
Prelude.Generic)

-- |
-- Create a value of 'AssociateMemberResponse' 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', 'associateMemberResponse_httpStatus' - The response's http status code.
--
-- 'accountId', 'associateMemberResponse_accountId' - The Amazon Web Services account ID of the successfully associated member
-- account.
newAssociateMemberResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'accountId'
  Prelude.Text ->
  AssociateMemberResponse
newAssociateMemberResponse :: Int -> Text -> AssociateMemberResponse
newAssociateMemberResponse Int
pHttpStatus_ Text
pAccountId_ =
  AssociateMemberResponse'
    { $sel:httpStatus:AssociateMemberResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:accountId:AssociateMemberResponse' :: Text
accountId = Text
pAccountId_
    }

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

-- | The Amazon Web Services account ID of the successfully associated member
-- account.
associateMemberResponse_accountId :: Lens.Lens' AssociateMemberResponse Prelude.Text
associateMemberResponse_accountId :: Lens' AssociateMemberResponse Text
associateMemberResponse_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMemberResponse' {Text
accountId :: Text
$sel:accountId:AssociateMemberResponse' :: AssociateMemberResponse -> Text
accountId} -> Text
accountId) (\s :: AssociateMemberResponse
s@AssociateMemberResponse' {} Text
a -> AssociateMemberResponse
s {$sel:accountId:AssociateMemberResponse' :: Text
accountId = Text
a} :: AssociateMemberResponse)

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