{-# 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.StopProductSubscription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops a product subscription for a user with the specified identity
-- provider.
module Amazonka.LicenseManagerUserSubscriptions.StopProductSubscription
  ( -- * Creating a Request
    StopProductSubscription (..),
    newStopProductSubscription,

    -- * Request Lenses
    stopProductSubscription_domain,
    stopProductSubscription_identityProvider,
    stopProductSubscription_product,
    stopProductSubscription_username,

    -- * Destructuring the Response
    StopProductSubscriptionResponse (..),
    newStopProductSubscriptionResponse,

    -- * Response Lenses
    stopProductSubscriptionResponse_httpStatus,
    stopProductSubscriptionResponse_productUserSummary,
  )
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:/ 'newStopProductSubscription' smart constructor.
data StopProductSubscription = StopProductSubscription'
  { -- | The domain name of the user.
    StopProductSubscription -> Maybe Text
domain :: Prelude.Maybe Prelude.Text,
    -- | An object that specifies details for the identity provider.
    StopProductSubscription -> IdentityProvider
identityProvider :: IdentityProvider,
    -- | The name of the user-based subscription product.
    StopProductSubscription -> Text
product :: Prelude.Text,
    -- | The user name from the identity provider for the user.
    StopProductSubscription -> Text
username :: Prelude.Text
  }
  deriving (StopProductSubscription -> StopProductSubscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopProductSubscription -> StopProductSubscription -> Bool
$c/= :: StopProductSubscription -> StopProductSubscription -> Bool
== :: StopProductSubscription -> StopProductSubscription -> Bool
$c== :: StopProductSubscription -> StopProductSubscription -> Bool
Prelude.Eq, ReadPrec [StopProductSubscription]
ReadPrec StopProductSubscription
Int -> ReadS StopProductSubscription
ReadS [StopProductSubscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopProductSubscription]
$creadListPrec :: ReadPrec [StopProductSubscription]
readPrec :: ReadPrec StopProductSubscription
$creadPrec :: ReadPrec StopProductSubscription
readList :: ReadS [StopProductSubscription]
$creadList :: ReadS [StopProductSubscription]
readsPrec :: Int -> ReadS StopProductSubscription
$creadsPrec :: Int -> ReadS StopProductSubscription
Prelude.Read, Int -> StopProductSubscription -> ShowS
[StopProductSubscription] -> ShowS
StopProductSubscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopProductSubscription] -> ShowS
$cshowList :: [StopProductSubscription] -> ShowS
show :: StopProductSubscription -> String
$cshow :: StopProductSubscription -> String
showsPrec :: Int -> StopProductSubscription -> ShowS
$cshowsPrec :: Int -> StopProductSubscription -> ShowS
Prelude.Show, forall x. Rep StopProductSubscription x -> StopProductSubscription
forall x. StopProductSubscription -> Rep StopProductSubscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopProductSubscription x -> StopProductSubscription
$cfrom :: forall x. StopProductSubscription -> Rep StopProductSubscription x
Prelude.Generic)

-- |
-- Create a value of 'StopProductSubscription' 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', 'stopProductSubscription_domain' - The domain name of the user.
--
-- 'identityProvider', 'stopProductSubscription_identityProvider' - An object that specifies details for the identity provider.
--
-- 'product', 'stopProductSubscription_product' - The name of the user-based subscription product.
--
-- 'username', 'stopProductSubscription_username' - The user name from the identity provider for the user.
newStopProductSubscription ::
  -- | 'identityProvider'
  IdentityProvider ->
  -- | 'product'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  StopProductSubscription
newStopProductSubscription :: IdentityProvider -> Text -> Text -> StopProductSubscription
newStopProductSubscription
  IdentityProvider
pIdentityProvider_
  Text
pProduct_
  Text
pUsername_ =
    StopProductSubscription'
      { $sel:domain:StopProductSubscription' :: Maybe Text
domain = forall a. Maybe a
Prelude.Nothing,
        $sel:identityProvider:StopProductSubscription' :: IdentityProvider
identityProvider = IdentityProvider
pIdentityProvider_,
        $sel:product:StopProductSubscription' :: Text
product = Text
pProduct_,
        $sel:username:StopProductSubscription' :: Text
username = Text
pUsername_
      }

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

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

-- | The name of the user-based subscription product.
stopProductSubscription_product :: Lens.Lens' StopProductSubscription Prelude.Text
stopProductSubscription_product :: Lens' StopProductSubscription Text
stopProductSubscription_product = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopProductSubscription' {Text
product :: Text
$sel:product:StopProductSubscription' :: StopProductSubscription -> Text
product} -> Text
product) (\s :: StopProductSubscription
s@StopProductSubscription' {} Text
a -> StopProductSubscription
s {$sel:product:StopProductSubscription' :: Text
product = Text
a} :: StopProductSubscription)

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

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

instance Prelude.Hashable StopProductSubscription where
  hashWithSalt :: Int -> StopProductSubscription -> Int
hashWithSalt Int
_salt StopProductSubscription' {Maybe Text
Text
IdentityProvider
username :: Text
product :: Text
identityProvider :: IdentityProvider
domain :: Maybe Text
$sel:username:StopProductSubscription' :: StopProductSubscription -> Text
$sel:product:StopProductSubscription' :: StopProductSubscription -> Text
$sel:identityProvider:StopProductSubscription' :: StopProductSubscription -> IdentityProvider
$sel:domain:StopProductSubscription' :: StopProductSubscription -> 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
product
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
username

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

instance Data.ToHeaders StopProductSubscription where
  toHeaders :: StopProductSubscription -> 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 StopProductSubscription where
  toJSON :: StopProductSubscription -> Value
toJSON StopProductSubscription' {Maybe Text
Text
IdentityProvider
username :: Text
product :: Text
identityProvider :: IdentityProvider
domain :: Maybe Text
$sel:username:StopProductSubscription' :: StopProductSubscription -> Text
$sel:product:StopProductSubscription' :: StopProductSubscription -> Text
$sel:identityProvider:StopProductSubscription' :: StopProductSubscription -> IdentityProvider
$sel:domain:StopProductSubscription' :: StopProductSubscription -> 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
"Product" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
product),
            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 StopProductSubscription where
  toPath :: StopProductSubscription -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/user/StopProductSubscription"

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

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

-- |
-- Create a value of 'StopProductSubscriptionResponse' 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', 'stopProductSubscriptionResponse_httpStatus' - The response's http status code.
--
-- 'productUserSummary', 'stopProductSubscriptionResponse_productUserSummary' - Metadata that describes the start product subscription operation.
newStopProductSubscriptionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'productUserSummary'
  ProductUserSummary ->
  StopProductSubscriptionResponse
newStopProductSubscriptionResponse :: Int -> ProductUserSummary -> StopProductSubscriptionResponse
newStopProductSubscriptionResponse
  Int
pHttpStatus_
  ProductUserSummary
pProductUserSummary_ =
    StopProductSubscriptionResponse'
      { $sel:httpStatus:StopProductSubscriptionResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:productUserSummary:StopProductSubscriptionResponse' :: ProductUserSummary
productUserSummary = ProductUserSummary
pProductUserSummary_
      }

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

-- | Metadata that describes the start product subscription operation.
stopProductSubscriptionResponse_productUserSummary :: Lens.Lens' StopProductSubscriptionResponse ProductUserSummary
stopProductSubscriptionResponse_productUserSummary :: Lens' StopProductSubscriptionResponse ProductUserSummary
stopProductSubscriptionResponse_productUserSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopProductSubscriptionResponse' {ProductUserSummary
productUserSummary :: ProductUserSummary
$sel:productUserSummary:StopProductSubscriptionResponse' :: StopProductSubscriptionResponse -> ProductUserSummary
productUserSummary} -> ProductUserSummary
productUserSummary) (\s :: StopProductSubscriptionResponse
s@StopProductSubscriptionResponse' {} ProductUserSummary
a -> StopProductSubscriptionResponse
s {$sel:productUserSummary:StopProductSubscriptionResponse' :: ProductUserSummary
productUserSummary = ProductUserSummary
a} :: StopProductSubscriptionResponse)

instance
  Prelude.NFData
    StopProductSubscriptionResponse
  where
  rnf :: StopProductSubscriptionResponse -> ()
rnf StopProductSubscriptionResponse' {Int
ProductUserSummary
productUserSummary :: ProductUserSummary
httpStatus :: Int
$sel:productUserSummary:StopProductSubscriptionResponse' :: StopProductSubscriptionResponse -> ProductUserSummary
$sel:httpStatus:StopProductSubscriptionResponse' :: StopProductSubscriptionResponse -> 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 ProductUserSummary
productUserSummary