{-# 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.LicenseManagerUserSubscriptions.DisassociateUser
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disassociates the user from an EC2 instance providing user-based
-- subscriptions.
module Amazonka.LicenseManagerUserSubscriptions.DisassociateUser
  ( -- * Creating a Request
    DisassociateUser (..),
    newDisassociateUser,

    -- * Request Lenses
    disassociateUser_domain,
    disassociateUser_identityProvider,
    disassociateUser_instanceId,
    disassociateUser_username,

    -- * Destructuring the Response
    DisassociateUserResponse (..),
    newDisassociateUserResponse,

    -- * Response Lenses
    disassociateUserResponse_httpStatus,
    disassociateUserResponse_instanceUserSummary,
  )
where

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

-- | /See:/ 'newDisassociateUser' smart constructor.
data DisassociateUser = DisassociateUser'
  { -- | The domain name of the user.
    DisassociateUser -> Maybe Text
domain :: Prelude.Maybe Prelude.Text,
    -- | An object that specifies details for the identity provider.
    DisassociateUser -> IdentityProvider
identityProvider :: IdentityProvider,
    -- | The ID of the EC2 instance, which provides user-based subscriptions.
    DisassociateUser -> Text
instanceId :: Prelude.Text,
    -- | The user name from the identity provider for the user.
    DisassociateUser -> Text
username :: Prelude.Text
  }
  deriving (DisassociateUser -> DisassociateUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateUser -> DisassociateUser -> Bool
$c/= :: DisassociateUser -> DisassociateUser -> Bool
== :: DisassociateUser -> DisassociateUser -> Bool
$c== :: DisassociateUser -> DisassociateUser -> Bool
Prelude.Eq, ReadPrec [DisassociateUser]
ReadPrec DisassociateUser
Int -> ReadS DisassociateUser
ReadS [DisassociateUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateUser]
$creadListPrec :: ReadPrec [DisassociateUser]
readPrec :: ReadPrec DisassociateUser
$creadPrec :: ReadPrec DisassociateUser
readList :: ReadS [DisassociateUser]
$creadList :: ReadS [DisassociateUser]
readsPrec :: Int -> ReadS DisassociateUser
$creadsPrec :: Int -> ReadS DisassociateUser
Prelude.Read, Int -> DisassociateUser -> ShowS
[DisassociateUser] -> ShowS
DisassociateUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateUser] -> ShowS
$cshowList :: [DisassociateUser] -> ShowS
show :: DisassociateUser -> String
$cshow :: DisassociateUser -> String
showsPrec :: Int -> DisassociateUser -> ShowS
$cshowsPrec :: Int -> DisassociateUser -> ShowS
Prelude.Show, forall x. Rep DisassociateUser x -> DisassociateUser
forall x. DisassociateUser -> Rep DisassociateUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisassociateUser x -> DisassociateUser
$cfrom :: forall x. DisassociateUser -> Rep DisassociateUser x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateUser' 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:
--
-- 'domain', 'disassociateUser_domain' - The domain name of the user.
--
-- 'identityProvider', 'disassociateUser_identityProvider' - An object that specifies details for the identity provider.
--
-- 'instanceId', 'disassociateUser_instanceId' - The ID of the EC2 instance, which provides user-based subscriptions.
--
-- 'username', 'disassociateUser_username' - The user name from the identity provider for the user.
newDisassociateUser ::
  -- | 'identityProvider'
  IdentityProvider ->
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  DisassociateUser
newDisassociateUser :: IdentityProvider -> Text -> Text -> DisassociateUser
newDisassociateUser
  IdentityProvider
pIdentityProvider_
  Text
pInstanceId_
  Text
pUsername_ =
    DisassociateUser'
      { $sel:domain:DisassociateUser' :: Maybe Text
domain = forall a. Maybe a
Prelude.Nothing,
        $sel:identityProvider:DisassociateUser' :: IdentityProvider
identityProvider = IdentityProvider
pIdentityProvider_,
        $sel:instanceId:DisassociateUser' :: Text
instanceId = Text
pInstanceId_,
        $sel:username:DisassociateUser' :: Text
username = Text
pUsername_
      }

-- | The domain name of the user.
disassociateUser_domain :: Lens.Lens' DisassociateUser (Prelude.Maybe Prelude.Text)
disassociateUser_domain :: Lens' DisassociateUser (Maybe Text)
disassociateUser_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateUser' {Maybe Text
domain :: Maybe Text
$sel:domain:DisassociateUser' :: DisassociateUser -> Maybe Text
domain} -> Maybe Text
domain) (\s :: DisassociateUser
s@DisassociateUser' {} Maybe Text
a -> DisassociateUser
s {$sel:domain:DisassociateUser' :: Maybe Text
domain = Maybe Text
a} :: DisassociateUser)

-- | An object that specifies details for the identity provider.
disassociateUser_identityProvider :: Lens.Lens' DisassociateUser IdentityProvider
disassociateUser_identityProvider :: Lens' DisassociateUser IdentityProvider
disassociateUser_identityProvider = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateUser' {IdentityProvider
identityProvider :: IdentityProvider
$sel:identityProvider:DisassociateUser' :: DisassociateUser -> IdentityProvider
identityProvider} -> IdentityProvider
identityProvider) (\s :: DisassociateUser
s@DisassociateUser' {} IdentityProvider
a -> DisassociateUser
s {$sel:identityProvider:DisassociateUser' :: IdentityProvider
identityProvider = IdentityProvider
a} :: DisassociateUser)

-- | The ID of the EC2 instance, which provides user-based subscriptions.
disassociateUser_instanceId :: Lens.Lens' DisassociateUser Prelude.Text
disassociateUser_instanceId :: Lens' DisassociateUser Text
disassociateUser_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateUser' {Text
instanceId :: Text
$sel:instanceId:DisassociateUser' :: DisassociateUser -> Text
instanceId} -> Text
instanceId) (\s :: DisassociateUser
s@DisassociateUser' {} Text
a -> DisassociateUser
s {$sel:instanceId:DisassociateUser' :: Text
instanceId = Text
a} :: DisassociateUser)

-- | The user name from the identity provider for the user.
disassociateUser_username :: Lens.Lens' DisassociateUser Prelude.Text
disassociateUser_username :: Lens' DisassociateUser Text
disassociateUser_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateUser' {Text
username :: Text
$sel:username:DisassociateUser' :: DisassociateUser -> Text
username} -> Text
username) (\s :: DisassociateUser
s@DisassociateUser' {} Text
a -> DisassociateUser
s {$sel:username:DisassociateUser' :: Text
username = Text
a} :: DisassociateUser)

instance Core.AWSRequest DisassociateUser where
  type
    AWSResponse DisassociateUser =
      DisassociateUserResponse
  request :: (Service -> Service)
-> DisassociateUser -> Request DisassociateUser
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 DisassociateUser
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DisassociateUser)))
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 -> InstanceUserSummary -> DisassociateUserResponse
DisassociateUserResponse'
            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
"InstanceUserSummary")
      )

instance Prelude.Hashable DisassociateUser where
  hashWithSalt :: Int -> DisassociateUser -> Int
hashWithSalt Int
_salt DisassociateUser' {Maybe Text
Text
IdentityProvider
username :: Text
instanceId :: Text
identityProvider :: IdentityProvider
domain :: Maybe Text
$sel:username:DisassociateUser' :: DisassociateUser -> Text
$sel:instanceId:DisassociateUser' :: DisassociateUser -> Text
$sel:identityProvider:DisassociateUser' :: DisassociateUser -> IdentityProvider
$sel:domain:DisassociateUser' :: DisassociateUser -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IdentityProvider
identityProvider
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
username

instance Prelude.NFData DisassociateUser where
  rnf :: DisassociateUser -> ()
rnf DisassociateUser' {Maybe Text
Text
IdentityProvider
username :: Text
instanceId :: Text
identityProvider :: IdentityProvider
domain :: Maybe Text
$sel:username:DisassociateUser' :: DisassociateUser -> Text
$sel:instanceId:DisassociateUser' :: DisassociateUser -> Text
$sel:identityProvider:DisassociateUser' :: DisassociateUser -> IdentityProvider
$sel:domain:DisassociateUser' :: DisassociateUser -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IdentityProvider
identityProvider
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
username

instance Data.ToHeaders DisassociateUser where
  toHeaders :: DisassociateUser -> 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 DisassociateUser where
  toJSON :: DisassociateUser -> Value
toJSON DisassociateUser' {Maybe Text
Text
IdentityProvider
username :: Text
instanceId :: Text
identityProvider :: IdentityProvider
domain :: Maybe Text
$sel:username:DisassociateUser' :: DisassociateUser -> Text
$sel:instanceId:DisassociateUser' :: DisassociateUser -> Text
$sel:identityProvider:DisassociateUser' :: DisassociateUser -> IdentityProvider
$sel:domain:DisassociateUser' :: DisassociateUser -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Domain" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
domain,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"IdentityProvider" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= IdentityProvider
identityProvider),
            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
"Username" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
username)
          ]
      )

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

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

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

-- |
-- Create a value of 'DisassociateUserResponse' 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', 'disassociateUserResponse_httpStatus' - The response's http status code.
--
-- 'instanceUserSummary', 'disassociateUserResponse_instanceUserSummary' - Metadata that describes the associate user operation.
newDisassociateUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'instanceUserSummary'
  InstanceUserSummary ->
  DisassociateUserResponse
newDisassociateUserResponse :: Int -> InstanceUserSummary -> DisassociateUserResponse
newDisassociateUserResponse
  Int
pHttpStatus_
  InstanceUserSummary
pInstanceUserSummary_ =
    DisassociateUserResponse'
      { $sel:httpStatus:DisassociateUserResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:instanceUserSummary:DisassociateUserResponse' :: InstanceUserSummary
instanceUserSummary = InstanceUserSummary
pInstanceUserSummary_
      }

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

-- | Metadata that describes the associate user operation.
disassociateUserResponse_instanceUserSummary :: Lens.Lens' DisassociateUserResponse InstanceUserSummary
disassociateUserResponse_instanceUserSummary :: Lens' DisassociateUserResponse InstanceUserSummary
disassociateUserResponse_instanceUserSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateUserResponse' {InstanceUserSummary
instanceUserSummary :: InstanceUserSummary
$sel:instanceUserSummary:DisassociateUserResponse' :: DisassociateUserResponse -> InstanceUserSummary
instanceUserSummary} -> InstanceUserSummary
instanceUserSummary) (\s :: DisassociateUserResponse
s@DisassociateUserResponse' {} InstanceUserSummary
a -> DisassociateUserResponse
s {$sel:instanceUserSummary:DisassociateUserResponse' :: InstanceUserSummary
instanceUserSummary = InstanceUserSummary
a} :: DisassociateUserResponse)

instance Prelude.NFData DisassociateUserResponse where
  rnf :: DisassociateUserResponse -> ()
rnf DisassociateUserResponse' {Int
InstanceUserSummary
instanceUserSummary :: InstanceUserSummary
httpStatus :: Int
$sel:instanceUserSummary:DisassociateUserResponse' :: DisassociateUserResponse -> InstanceUserSummary
$sel:httpStatus:DisassociateUserResponse' :: DisassociateUserResponse -> 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 InstanceUserSummary
instanceUserSummary