{-# 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.Detective.DisassociateMembership
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes the member account from the specified behavior graph. This
-- operation can only be called by an invited member account that has the
-- @ENABLED@ status.
--
-- @DisassociateMembership@ cannot be called by an organization account in
-- the organization behavior graph. For the organization behavior graph,
-- the Detective administrator account determines which organization
-- accounts to enable or disable as member accounts.
module Amazonka.Detective.DisassociateMembership
  ( -- * Creating a Request
    DisassociateMembership (..),
    newDisassociateMembership,

    -- * Request Lenses
    disassociateMembership_graphArn,

    -- * Destructuring the Response
    DisassociateMembershipResponse (..),
    newDisassociateMembershipResponse,
  )
where

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

-- | /See:/ 'newDisassociateMembership' smart constructor.
data DisassociateMembership = DisassociateMembership'
  { -- | The ARN of the behavior graph to remove the member account from.
    --
    -- The member account\'s member status in the behavior graph must be
    -- @ENABLED@.
    DisassociateMembership -> Text
graphArn :: Prelude.Text
  }
  deriving (DisassociateMembership -> DisassociateMembership -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateMembership -> DisassociateMembership -> Bool
$c/= :: DisassociateMembership -> DisassociateMembership -> Bool
== :: DisassociateMembership -> DisassociateMembership -> Bool
$c== :: DisassociateMembership -> DisassociateMembership -> Bool
Prelude.Eq, ReadPrec [DisassociateMembership]
ReadPrec DisassociateMembership
Int -> ReadS DisassociateMembership
ReadS [DisassociateMembership]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateMembership]
$creadListPrec :: ReadPrec [DisassociateMembership]
readPrec :: ReadPrec DisassociateMembership
$creadPrec :: ReadPrec DisassociateMembership
readList :: ReadS [DisassociateMembership]
$creadList :: ReadS [DisassociateMembership]
readsPrec :: Int -> ReadS DisassociateMembership
$creadsPrec :: Int -> ReadS DisassociateMembership
Prelude.Read, Int -> DisassociateMembership -> ShowS
[DisassociateMembership] -> ShowS
DisassociateMembership -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateMembership] -> ShowS
$cshowList :: [DisassociateMembership] -> ShowS
show :: DisassociateMembership -> String
$cshow :: DisassociateMembership -> String
showsPrec :: Int -> DisassociateMembership -> ShowS
$cshowsPrec :: Int -> DisassociateMembership -> ShowS
Prelude.Show, forall x. Rep DisassociateMembership x -> DisassociateMembership
forall x. DisassociateMembership -> Rep DisassociateMembership x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisassociateMembership x -> DisassociateMembership
$cfrom :: forall x. DisassociateMembership -> Rep DisassociateMembership x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateMembership' 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:
--
-- 'graphArn', 'disassociateMembership_graphArn' - The ARN of the behavior graph to remove the member account from.
--
-- The member account\'s member status in the behavior graph must be
-- @ENABLED@.
newDisassociateMembership ::
  -- | 'graphArn'
  Prelude.Text ->
  DisassociateMembership
newDisassociateMembership :: Text -> DisassociateMembership
newDisassociateMembership Text
pGraphArn_ =
  DisassociateMembership' {$sel:graphArn:DisassociateMembership' :: Text
graphArn = Text
pGraphArn_}

-- | The ARN of the behavior graph to remove the member account from.
--
-- The member account\'s member status in the behavior graph must be
-- @ENABLED@.
disassociateMembership_graphArn :: Lens.Lens' DisassociateMembership Prelude.Text
disassociateMembership_graphArn :: Lens' DisassociateMembership Text
disassociateMembership_graphArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateMembership' {Text
graphArn :: Text
$sel:graphArn:DisassociateMembership' :: DisassociateMembership -> Text
graphArn} -> Text
graphArn) (\s :: DisassociateMembership
s@DisassociateMembership' {} Text
a -> DisassociateMembership
s {$sel:graphArn:DisassociateMembership' :: Text
graphArn = Text
a} :: DisassociateMembership)

instance Core.AWSRequest DisassociateMembership where
  type
    AWSResponse DisassociateMembership =
      DisassociateMembershipResponse
  request :: (Service -> Service)
-> DisassociateMembership -> Request DisassociateMembership
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 DisassociateMembership
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateMembership)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DisassociateMembershipResponse
DisassociateMembershipResponse'

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

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

instance Data.ToHeaders DisassociateMembership where
  toHeaders :: DisassociateMembership -> [Header]
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 -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

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

-- |
-- Create a value of 'DisassociateMembershipResponse' 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.
newDisassociateMembershipResponse ::
  DisassociateMembershipResponse
newDisassociateMembershipResponse :: DisassociateMembershipResponse
newDisassociateMembershipResponse =
  DisassociateMembershipResponse
DisassociateMembershipResponse'

instance
  Prelude.NFData
    DisassociateMembershipResponse
  where
  rnf :: DisassociateMembershipResponse -> ()
rnf DisassociateMembershipResponse
_ = ()