{-# 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.MarketplaceMetering.ResolveCustomer
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- @ResolveCustomer@ is called by a SaaS application during the
-- registration process. When a buyer visits your website during the
-- registration process, the buyer submits a registration token through
-- their browser. The registration token is resolved through this API to
-- obtain a @CustomerIdentifier@ along with the @CustomerAWSAccountId@ and
-- @ProductCode@.
--
-- The API needs to called from the seller account id used to publish the
-- SaaS application to successfully resolve the token.
--
-- For an example of using @ResolveCustomer@, see
-- <https://docs.aws.amazon.com/marketplace/latest/userguide/saas-code-examples.html#saas-resolvecustomer-example ResolveCustomer code example>
-- in the /AWS Marketplace Seller Guide/.
module Amazonka.MarketplaceMetering.ResolveCustomer
  ( -- * Creating a Request
    ResolveCustomer (..),
    newResolveCustomer,

    -- * Request Lenses
    resolveCustomer_registrationToken,

    -- * Destructuring the Response
    ResolveCustomerResponse (..),
    newResolveCustomerResponse,

    -- * Response Lenses
    resolveCustomerResponse_customerAWSAccountId,
    resolveCustomerResponse_customerIdentifier,
    resolveCustomerResponse_productCode,
    resolveCustomerResponse_httpStatus,
  )
where

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

-- | Contains input to the @ResolveCustomer@ operation.
--
-- /See:/ 'newResolveCustomer' smart constructor.
data ResolveCustomer = ResolveCustomer'
  { -- | When a buyer visits your website during the registration process, the
    -- buyer submits a registration token through the browser. The registration
    -- token is resolved to obtain a @CustomerIdentifier@ along with the
    -- @CustomerAWSAccountId@ and @ProductCode@.
    ResolveCustomer -> Text
registrationToken :: Prelude.Text
  }
  deriving (ResolveCustomer -> ResolveCustomer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResolveCustomer -> ResolveCustomer -> Bool
$c/= :: ResolveCustomer -> ResolveCustomer -> Bool
== :: ResolveCustomer -> ResolveCustomer -> Bool
$c== :: ResolveCustomer -> ResolveCustomer -> Bool
Prelude.Eq, ReadPrec [ResolveCustomer]
ReadPrec ResolveCustomer
Int -> ReadS ResolveCustomer
ReadS [ResolveCustomer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResolveCustomer]
$creadListPrec :: ReadPrec [ResolveCustomer]
readPrec :: ReadPrec ResolveCustomer
$creadPrec :: ReadPrec ResolveCustomer
readList :: ReadS [ResolveCustomer]
$creadList :: ReadS [ResolveCustomer]
readsPrec :: Int -> ReadS ResolveCustomer
$creadsPrec :: Int -> ReadS ResolveCustomer
Prelude.Read, Int -> ResolveCustomer -> ShowS
[ResolveCustomer] -> ShowS
ResolveCustomer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolveCustomer] -> ShowS
$cshowList :: [ResolveCustomer] -> ShowS
show :: ResolveCustomer -> String
$cshow :: ResolveCustomer -> String
showsPrec :: Int -> ResolveCustomer -> ShowS
$cshowsPrec :: Int -> ResolveCustomer -> ShowS
Prelude.Show, forall x. Rep ResolveCustomer x -> ResolveCustomer
forall x. ResolveCustomer -> Rep ResolveCustomer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResolveCustomer x -> ResolveCustomer
$cfrom :: forall x. ResolveCustomer -> Rep ResolveCustomer x
Prelude.Generic)

-- |
-- Create a value of 'ResolveCustomer' 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:
--
-- 'registrationToken', 'resolveCustomer_registrationToken' - When a buyer visits your website during the registration process, the
-- buyer submits a registration token through the browser. The registration
-- token is resolved to obtain a @CustomerIdentifier@ along with the
-- @CustomerAWSAccountId@ and @ProductCode@.
newResolveCustomer ::
  -- | 'registrationToken'
  Prelude.Text ->
  ResolveCustomer
newResolveCustomer :: Text -> ResolveCustomer
newResolveCustomer Text
pRegistrationToken_ =
  ResolveCustomer'
    { $sel:registrationToken:ResolveCustomer' :: Text
registrationToken =
        Text
pRegistrationToken_
    }

-- | When a buyer visits your website during the registration process, the
-- buyer submits a registration token through the browser. The registration
-- token is resolved to obtain a @CustomerIdentifier@ along with the
-- @CustomerAWSAccountId@ and @ProductCode@.
resolveCustomer_registrationToken :: Lens.Lens' ResolveCustomer Prelude.Text
resolveCustomer_registrationToken :: Lens' ResolveCustomer Text
resolveCustomer_registrationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResolveCustomer' {Text
registrationToken :: Text
$sel:registrationToken:ResolveCustomer' :: ResolveCustomer -> Text
registrationToken} -> Text
registrationToken) (\s :: ResolveCustomer
s@ResolveCustomer' {} Text
a -> ResolveCustomer
s {$sel:registrationToken:ResolveCustomer' :: Text
registrationToken = Text
a} :: ResolveCustomer)

instance Core.AWSRequest ResolveCustomer where
  type
    AWSResponse ResolveCustomer =
      ResolveCustomerResponse
  request :: (Service -> Service) -> ResolveCustomer -> Request ResolveCustomer
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 ResolveCustomer
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ResolveCustomer)))
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 ->
          Maybe Text
-> Maybe Text -> Maybe Text -> Int -> ResolveCustomerResponse
ResolveCustomerResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CustomerAWSAccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CustomerIdentifier")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ProductCode")
            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 ResolveCustomer where
  hashWithSalt :: Int -> ResolveCustomer -> Int
hashWithSalt Int
_salt ResolveCustomer' {Text
registrationToken :: Text
$sel:registrationToken:ResolveCustomer' :: ResolveCustomer -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
registrationToken

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

instance Data.ToHeaders ResolveCustomer where
  toHeaders :: ResolveCustomer -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSMPMeteringService.ResolveCustomer" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

-- | The result of the @ResolveCustomer@ operation. Contains the
-- @CustomerIdentifier@ along with the @CustomerAWSAccountId@ and
-- @ProductCode@.
--
-- /See:/ 'newResolveCustomerResponse' smart constructor.
data ResolveCustomerResponse = ResolveCustomerResponse'
  { -- | The @CustomerAWSAccountId@ provides the AWS account ID associated with
    -- the @CustomerIdentifier@ for the individual customer.
    ResolveCustomerResponse -> Maybe Text
customerAWSAccountId :: Prelude.Maybe Prelude.Text,
    -- | The @CustomerIdentifier@ is used to identify an individual customer in
    -- your application. Calls to @BatchMeterUsage@ require
    -- @CustomerIdentifiers@ for each @UsageRecord@.
    ResolveCustomerResponse -> Maybe Text
customerIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The product code is returned to confirm that the buyer is registering
    -- for your product. Subsequent @BatchMeterUsage@ calls should be made
    -- using this product code.
    ResolveCustomerResponse -> Maybe Text
productCode :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ResolveCustomerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ResolveCustomerResponse -> ResolveCustomerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResolveCustomerResponse -> ResolveCustomerResponse -> Bool
$c/= :: ResolveCustomerResponse -> ResolveCustomerResponse -> Bool
== :: ResolveCustomerResponse -> ResolveCustomerResponse -> Bool
$c== :: ResolveCustomerResponse -> ResolveCustomerResponse -> Bool
Prelude.Eq, ReadPrec [ResolveCustomerResponse]
ReadPrec ResolveCustomerResponse
Int -> ReadS ResolveCustomerResponse
ReadS [ResolveCustomerResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResolveCustomerResponse]
$creadListPrec :: ReadPrec [ResolveCustomerResponse]
readPrec :: ReadPrec ResolveCustomerResponse
$creadPrec :: ReadPrec ResolveCustomerResponse
readList :: ReadS [ResolveCustomerResponse]
$creadList :: ReadS [ResolveCustomerResponse]
readsPrec :: Int -> ReadS ResolveCustomerResponse
$creadsPrec :: Int -> ReadS ResolveCustomerResponse
Prelude.Read, Int -> ResolveCustomerResponse -> ShowS
[ResolveCustomerResponse] -> ShowS
ResolveCustomerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolveCustomerResponse] -> ShowS
$cshowList :: [ResolveCustomerResponse] -> ShowS
show :: ResolveCustomerResponse -> String
$cshow :: ResolveCustomerResponse -> String
showsPrec :: Int -> ResolveCustomerResponse -> ShowS
$cshowsPrec :: Int -> ResolveCustomerResponse -> ShowS
Prelude.Show, forall x. Rep ResolveCustomerResponse x -> ResolveCustomerResponse
forall x. ResolveCustomerResponse -> Rep ResolveCustomerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResolveCustomerResponse x -> ResolveCustomerResponse
$cfrom :: forall x. ResolveCustomerResponse -> Rep ResolveCustomerResponse x
Prelude.Generic)

-- |
-- Create a value of 'ResolveCustomerResponse' 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:
--
-- 'customerAWSAccountId', 'resolveCustomerResponse_customerAWSAccountId' - The @CustomerAWSAccountId@ provides the AWS account ID associated with
-- the @CustomerIdentifier@ for the individual customer.
--
-- 'customerIdentifier', 'resolveCustomerResponse_customerIdentifier' - The @CustomerIdentifier@ is used to identify an individual customer in
-- your application. Calls to @BatchMeterUsage@ require
-- @CustomerIdentifiers@ for each @UsageRecord@.
--
-- 'productCode', 'resolveCustomerResponse_productCode' - The product code is returned to confirm that the buyer is registering
-- for your product. Subsequent @BatchMeterUsage@ calls should be made
-- using this product code.
--
-- 'httpStatus', 'resolveCustomerResponse_httpStatus' - The response's http status code.
newResolveCustomerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ResolveCustomerResponse
newResolveCustomerResponse :: Int -> ResolveCustomerResponse
newResolveCustomerResponse Int
pHttpStatus_ =
  ResolveCustomerResponse'
    { $sel:customerAWSAccountId:ResolveCustomerResponse' :: Maybe Text
customerAWSAccountId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:customerIdentifier:ResolveCustomerResponse' :: Maybe Text
customerIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:productCode:ResolveCustomerResponse' :: Maybe Text
productCode = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ResolveCustomerResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @CustomerAWSAccountId@ provides the AWS account ID associated with
-- the @CustomerIdentifier@ for the individual customer.
resolveCustomerResponse_customerAWSAccountId :: Lens.Lens' ResolveCustomerResponse (Prelude.Maybe Prelude.Text)
resolveCustomerResponse_customerAWSAccountId :: Lens' ResolveCustomerResponse (Maybe Text)
resolveCustomerResponse_customerAWSAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResolveCustomerResponse' {Maybe Text
customerAWSAccountId :: Maybe Text
$sel:customerAWSAccountId:ResolveCustomerResponse' :: ResolveCustomerResponse -> Maybe Text
customerAWSAccountId} -> Maybe Text
customerAWSAccountId) (\s :: ResolveCustomerResponse
s@ResolveCustomerResponse' {} Maybe Text
a -> ResolveCustomerResponse
s {$sel:customerAWSAccountId:ResolveCustomerResponse' :: Maybe Text
customerAWSAccountId = Maybe Text
a} :: ResolveCustomerResponse)

-- | The @CustomerIdentifier@ is used to identify an individual customer in
-- your application. Calls to @BatchMeterUsage@ require
-- @CustomerIdentifiers@ for each @UsageRecord@.
resolveCustomerResponse_customerIdentifier :: Lens.Lens' ResolveCustomerResponse (Prelude.Maybe Prelude.Text)
resolveCustomerResponse_customerIdentifier :: Lens' ResolveCustomerResponse (Maybe Text)
resolveCustomerResponse_customerIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResolveCustomerResponse' {Maybe Text
customerIdentifier :: Maybe Text
$sel:customerIdentifier:ResolveCustomerResponse' :: ResolveCustomerResponse -> Maybe Text
customerIdentifier} -> Maybe Text
customerIdentifier) (\s :: ResolveCustomerResponse
s@ResolveCustomerResponse' {} Maybe Text
a -> ResolveCustomerResponse
s {$sel:customerIdentifier:ResolveCustomerResponse' :: Maybe Text
customerIdentifier = Maybe Text
a} :: ResolveCustomerResponse)

-- | The product code is returned to confirm that the buyer is registering
-- for your product. Subsequent @BatchMeterUsage@ calls should be made
-- using this product code.
resolveCustomerResponse_productCode :: Lens.Lens' ResolveCustomerResponse (Prelude.Maybe Prelude.Text)
resolveCustomerResponse_productCode :: Lens' ResolveCustomerResponse (Maybe Text)
resolveCustomerResponse_productCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResolveCustomerResponse' {Maybe Text
productCode :: Maybe Text
$sel:productCode:ResolveCustomerResponse' :: ResolveCustomerResponse -> Maybe Text
productCode} -> Maybe Text
productCode) (\s :: ResolveCustomerResponse
s@ResolveCustomerResponse' {} Maybe Text
a -> ResolveCustomerResponse
s {$sel:productCode:ResolveCustomerResponse' :: Maybe Text
productCode = Maybe Text
a} :: ResolveCustomerResponse)

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

instance Prelude.NFData ResolveCustomerResponse where
  rnf :: ResolveCustomerResponse -> ()
rnf ResolveCustomerResponse' {Int
Maybe Text
httpStatus :: Int
productCode :: Maybe Text
customerIdentifier :: Maybe Text
customerAWSAccountId :: Maybe Text
$sel:httpStatus:ResolveCustomerResponse' :: ResolveCustomerResponse -> Int
$sel:productCode:ResolveCustomerResponse' :: ResolveCustomerResponse -> Maybe Text
$sel:customerIdentifier:ResolveCustomerResponse' :: ResolveCustomerResponse -> Maybe Text
$sel:customerAWSAccountId:ResolveCustomerResponse' :: ResolveCustomerResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customerAWSAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customerIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
productCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus