{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- |
-- Module      : Gogol.AppsLicensing.Licensing.LicenseAssignments.ListForProduct
-- Copyright   : (c) 2015-2025 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay <brendan.g.hay+gogol@gmail.com>
--               Toni Cebrián <toni@tonicebrian.com>
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- List all users assigned licenses for a specific product SKU.
--
-- /See:/ <https://developers.google.com/admin-sdk/licensing/ Enterprise License Manager API Reference> for @licensing.licenseAssignments.listForProduct@.
module Gogol.AppsLicensing.Licensing.LicenseAssignments.ListForProduct
  ( -- * Resource
    LicensingLicenseAssignmentsListForProductResource,

    -- ** Constructing a Request
    LicensingLicenseAssignmentsListForProduct (..),
    newLicensingLicenseAssignmentsListForProduct,
  )
where

import Gogol.AppsLicensing.Types
import Gogol.Prelude qualified as Core

-- | A resource alias for @licensing.licenseAssignments.listForProduct@ method which the
-- 'LicensingLicenseAssignmentsListForProduct' request conforms to.
type LicensingLicenseAssignmentsListForProductResource =
  "apps"
    Core.:> "licensing"
    Core.:> "v1"
    Core.:> "product"
    Core.:> Core.Capture "productId" Core.Text
    Core.:> "users"
    Core.:> Core.QueryParam "customerId" Core.Text
    Core.:> Core.QueryParam "$.xgafv" Xgafv
    Core.:> Core.QueryParam "access_token" Core.Text
    Core.:> Core.QueryParam "callback" Core.Text
    Core.:> Core.QueryParam "maxResults" Core.Word32
    Core.:> Core.QueryParam "pageToken" Core.Text
    Core.:> Core.QueryParam "uploadType" Core.Text
    Core.:> Core.QueryParam "upload_protocol" Core.Text
    Core.:> Core.QueryParam "alt" Core.AltJSON
    Core.:> Core.Get '[Core.JSON] LicenseAssignmentList

-- | List all users assigned licenses for a specific product SKU.
--
-- /See:/ 'newLicensingLicenseAssignmentsListForProduct' smart constructor.
data LicensingLicenseAssignmentsListForProduct = LicensingLicenseAssignmentsListForProduct
  { -- | V1 error format.
    LicensingLicenseAssignmentsListForProduct -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
    -- | OAuth access token.
    LicensingLicenseAssignmentsListForProduct -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
    -- | JSONP
    LicensingLicenseAssignmentsListForProduct -> Maybe Text
callback :: (Core.Maybe Core.Text),
    -- | The customer\'s unique ID as defined in the Admin console, such as @C00000000@. If the customer is suspended, the server returns an error.
    LicensingLicenseAssignmentsListForProduct -> Text
customerId :: Core.Text,
    -- | The @maxResults@ query string determines how many entries are returned on each page of a large response. This is an optional parameter. The value must be a positive number.
    LicensingLicenseAssignmentsListForProduct -> Word32
maxResults :: Core.Word32,
    -- | Token to fetch the next page of data. The @maxResults@ query string is related to the @pageToken@ since @maxResults@ determines how many entries are returned on each page. This is an optional query string. If not specified, the server returns the first page.
    LicensingLicenseAssignmentsListForProduct -> Text
pageToken :: Core.Text,
    -- | A product\'s unique identifier. For more information about products in this version of the API, see Products and SKUs.
    LicensingLicenseAssignmentsListForProduct -> Text
productId :: Core.Text,
    -- | Legacy upload protocol for media (e.g. \"media\", \"multipart\").
    LicensingLicenseAssignmentsListForProduct -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
    -- | Upload protocol for media (e.g. \"raw\", \"multipart\").
    LicensingLicenseAssignmentsListForProduct -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text)
  }
  deriving (LicensingLicenseAssignmentsListForProduct
-> LicensingLicenseAssignmentsListForProduct -> Bool
(LicensingLicenseAssignmentsListForProduct
 -> LicensingLicenseAssignmentsListForProduct -> Bool)
-> (LicensingLicenseAssignmentsListForProduct
    -> LicensingLicenseAssignmentsListForProduct -> Bool)
-> Eq LicensingLicenseAssignmentsListForProduct
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LicensingLicenseAssignmentsListForProduct
-> LicensingLicenseAssignmentsListForProduct -> Bool
== :: LicensingLicenseAssignmentsListForProduct
-> LicensingLicenseAssignmentsListForProduct -> Bool
$c/= :: LicensingLicenseAssignmentsListForProduct
-> LicensingLicenseAssignmentsListForProduct -> Bool
/= :: LicensingLicenseAssignmentsListForProduct
-> LicensingLicenseAssignmentsListForProduct -> Bool
Core.Eq, Int -> LicensingLicenseAssignmentsListForProduct -> ShowS
[LicensingLicenseAssignmentsListForProduct] -> ShowS
LicensingLicenseAssignmentsListForProduct -> String
(Int -> LicensingLicenseAssignmentsListForProduct -> ShowS)
-> (LicensingLicenseAssignmentsListForProduct -> String)
-> ([LicensingLicenseAssignmentsListForProduct] -> ShowS)
-> Show LicensingLicenseAssignmentsListForProduct
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LicensingLicenseAssignmentsListForProduct -> ShowS
showsPrec :: Int -> LicensingLicenseAssignmentsListForProduct -> ShowS
$cshow :: LicensingLicenseAssignmentsListForProduct -> String
show :: LicensingLicenseAssignmentsListForProduct -> String
$cshowList :: [LicensingLicenseAssignmentsListForProduct] -> ShowS
showList :: [LicensingLicenseAssignmentsListForProduct] -> ShowS
Core.Show, (forall x.
 LicensingLicenseAssignmentsListForProduct
 -> Rep LicensingLicenseAssignmentsListForProduct x)
-> (forall x.
    Rep LicensingLicenseAssignmentsListForProduct x
    -> LicensingLicenseAssignmentsListForProduct)
-> Generic LicensingLicenseAssignmentsListForProduct
forall x.
Rep LicensingLicenseAssignmentsListForProduct x
-> LicensingLicenseAssignmentsListForProduct
forall x.
LicensingLicenseAssignmentsListForProduct
-> Rep LicensingLicenseAssignmentsListForProduct x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
LicensingLicenseAssignmentsListForProduct
-> Rep LicensingLicenseAssignmentsListForProduct x
from :: forall x.
LicensingLicenseAssignmentsListForProduct
-> Rep LicensingLicenseAssignmentsListForProduct x
$cto :: forall x.
Rep LicensingLicenseAssignmentsListForProduct x
-> LicensingLicenseAssignmentsListForProduct
to :: forall x.
Rep LicensingLicenseAssignmentsListForProduct x
-> LicensingLicenseAssignmentsListForProduct
Core.Generic)

-- | Creates a value of 'LicensingLicenseAssignmentsListForProduct' with the minimum fields required to make a request.
newLicensingLicenseAssignmentsListForProduct ::
  -- |  The customer\'s unique ID as defined in the Admin console, such as @C00000000@. If the customer is suspended, the server returns an error. See 'customerId'.
  Core.Text ->
  -- |  A product\'s unique identifier. For more information about products in this version of the API, see Products and SKUs. See 'productId'.
  Core.Text ->
  LicensingLicenseAssignmentsListForProduct
newLicensingLicenseAssignmentsListForProduct :: Text -> Text -> LicensingLicenseAssignmentsListForProduct
newLicensingLicenseAssignmentsListForProduct Text
customerId Text
productId =
  LicensingLicenseAssignmentsListForProduct
    { xgafv :: Maybe Xgafv
xgafv = Maybe Xgafv
forall a. Maybe a
Core.Nothing,
      accessToken :: Maybe Text
accessToken = Maybe Text
forall a. Maybe a
Core.Nothing,
      callback :: Maybe Text
callback = Maybe Text
forall a. Maybe a
Core.Nothing,
      customerId :: Text
customerId = Text
customerId,
      maxResults :: Word32
maxResults = Word32
100,
      pageToken :: Text
pageToken = Text
"",
      productId :: Text
productId = Text
productId,
      uploadType :: Maybe Text
uploadType = Maybe Text
forall a. Maybe a
Core.Nothing,
      uploadProtocol :: Maybe Text
uploadProtocol = Maybe Text
forall a. Maybe a
Core.Nothing
    }

instance
  Core.GoogleRequest
    LicensingLicenseAssignmentsListForProduct
  where
  type
    Rs LicensingLicenseAssignmentsListForProduct =
      LicenseAssignmentList
  type
    Scopes LicensingLicenseAssignmentsListForProduct =
      '[Apps'Licensing]
  requestClient :: LicensingLicenseAssignmentsListForProduct
-> GClient (Rs LicensingLicenseAssignmentsListForProduct)
requestClient LicensingLicenseAssignmentsListForProduct {Maybe Text
Maybe Xgafv
Word32
Text
xgafv :: LicensingLicenseAssignmentsListForProduct -> Maybe Xgafv
accessToken :: LicensingLicenseAssignmentsListForProduct -> Maybe Text
callback :: LicensingLicenseAssignmentsListForProduct -> Maybe Text
customerId :: LicensingLicenseAssignmentsListForProduct -> Text
maxResults :: LicensingLicenseAssignmentsListForProduct -> Word32
pageToken :: LicensingLicenseAssignmentsListForProduct -> Text
productId :: LicensingLicenseAssignmentsListForProduct -> Text
uploadType :: LicensingLicenseAssignmentsListForProduct -> Maybe Text
uploadProtocol :: LicensingLicenseAssignmentsListForProduct -> Maybe Text
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
customerId :: Text
maxResults :: Word32
pageToken :: Text
productId :: Text
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
..} =
    Text
-> Maybe Text
-> Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Word32
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AltJSON
-> ServiceConfig
-> GClient LicenseAssignmentList
go
      Text
productId
      (Text -> Maybe Text
forall a. a -> Maybe a
Core.Just Text
customerId)
      Maybe Xgafv
xgafv
      Maybe Text
accessToken
      Maybe Text
callback
      (Word32 -> Maybe Word32
forall a. a -> Maybe a
Core.Just Word32
maxResults)
      (Text -> Maybe Text
forall a. a -> Maybe a
Core.Just Text
pageToken)
      Maybe Text
uploadType
      Maybe Text
uploadProtocol
      (AltJSON -> Maybe AltJSON
forall a. a -> Maybe a
Core.Just AltJSON
Core.AltJSON)
      ServiceConfig
appsLicensingService
    where
      go :: Fn LicensingLicenseAssignmentsListForProductResource
go =
        Proxy LicensingLicenseAssignmentsListForProductResource
-> Request -> Fn LicensingLicenseAssignmentsListForProductResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
          ( Proxy LicensingLicenseAssignmentsListForProductResource
forall {k} (t :: k). Proxy t
Core.Proxy ::
              Core.Proxy LicensingLicenseAssignmentsListForProductResource
          )
          Request
forall a. Monoid a => a
Core.mempty