{-# 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.Patch
(
LicensingLicenseAssignmentsPatchResource,
LicensingLicenseAssignmentsPatch (..),
newLicensingLicenseAssignmentsPatch,
)
where
import Gogol.AppsLicensing.Types
import Gogol.Prelude qualified as Core
type LicensingLicenseAssignmentsPatchResource =
"apps"
Core.:> "licensing"
Core.:> "v1"
Core.:> "product"
Core.:> Core.Capture "productId" Core.Text
Core.:> "sku"
Core.:> Core.Capture "skuId" Core.Text
Core.:> "user"
Core.:> Core.Capture "userId" Core.Text
Core.:> Core.QueryParam "$.xgafv" Xgafv
Core.:> Core.QueryParam "access_token" Core.Text
Core.:> Core.QueryParam "callback" Core.Text
Core.:> Core.QueryParam "uploadType" Core.Text
Core.:> Core.QueryParam "upload_protocol" Core.Text
Core.:> Core.QueryParam "alt" Core.AltJSON
Core.:> Core.ReqBody '[Core.JSON] LicenseAssignment
Core.:> Core.Patch '[Core.JSON] LicenseAssignment
data LicensingLicenseAssignmentsPatch = LicensingLicenseAssignmentsPatch
{
LicensingLicenseAssignmentsPatch -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
LicensingLicenseAssignmentsPatch -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
LicensingLicenseAssignmentsPatch -> Maybe Text
callback :: (Core.Maybe Core.Text),
LicensingLicenseAssignmentsPatch -> LicenseAssignment
payload :: LicenseAssignment,
LicensingLicenseAssignmentsPatch -> Text
productId :: Core.Text,
LicensingLicenseAssignmentsPatch -> Text
skuId :: Core.Text,
LicensingLicenseAssignmentsPatch -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
LicensingLicenseAssignmentsPatch -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text),
LicensingLicenseAssignmentsPatch -> Text
userId :: Core.Text
}
deriving (LicensingLicenseAssignmentsPatch
-> LicensingLicenseAssignmentsPatch -> Bool
(LicensingLicenseAssignmentsPatch
-> LicensingLicenseAssignmentsPatch -> Bool)
-> (LicensingLicenseAssignmentsPatch
-> LicensingLicenseAssignmentsPatch -> Bool)
-> Eq LicensingLicenseAssignmentsPatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LicensingLicenseAssignmentsPatch
-> LicensingLicenseAssignmentsPatch -> Bool
== :: LicensingLicenseAssignmentsPatch
-> LicensingLicenseAssignmentsPatch -> Bool
$c/= :: LicensingLicenseAssignmentsPatch
-> LicensingLicenseAssignmentsPatch -> Bool
/= :: LicensingLicenseAssignmentsPatch
-> LicensingLicenseAssignmentsPatch -> Bool
Core.Eq, Int -> LicensingLicenseAssignmentsPatch -> ShowS
[LicensingLicenseAssignmentsPatch] -> ShowS
LicensingLicenseAssignmentsPatch -> String
(Int -> LicensingLicenseAssignmentsPatch -> ShowS)
-> (LicensingLicenseAssignmentsPatch -> String)
-> ([LicensingLicenseAssignmentsPatch] -> ShowS)
-> Show LicensingLicenseAssignmentsPatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LicensingLicenseAssignmentsPatch -> ShowS
showsPrec :: Int -> LicensingLicenseAssignmentsPatch -> ShowS
$cshow :: LicensingLicenseAssignmentsPatch -> String
show :: LicensingLicenseAssignmentsPatch -> String
$cshowList :: [LicensingLicenseAssignmentsPatch] -> ShowS
showList :: [LicensingLicenseAssignmentsPatch] -> ShowS
Core.Show, (forall x.
LicensingLicenseAssignmentsPatch
-> Rep LicensingLicenseAssignmentsPatch x)
-> (forall x.
Rep LicensingLicenseAssignmentsPatch x
-> LicensingLicenseAssignmentsPatch)
-> Generic LicensingLicenseAssignmentsPatch
forall x.
Rep LicensingLicenseAssignmentsPatch x
-> LicensingLicenseAssignmentsPatch
forall x.
LicensingLicenseAssignmentsPatch
-> Rep LicensingLicenseAssignmentsPatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
LicensingLicenseAssignmentsPatch
-> Rep LicensingLicenseAssignmentsPatch x
from :: forall x.
LicensingLicenseAssignmentsPatch
-> Rep LicensingLicenseAssignmentsPatch x
$cto :: forall x.
Rep LicensingLicenseAssignmentsPatch x
-> LicensingLicenseAssignmentsPatch
to :: forall x.
Rep LicensingLicenseAssignmentsPatch x
-> LicensingLicenseAssignmentsPatch
Core.Generic)
newLicensingLicenseAssignmentsPatch ::
LicenseAssignment ->
Core.Text ->
Core.Text ->
Core.Text ->
LicensingLicenseAssignmentsPatch
newLicensingLicenseAssignmentsPatch :: LicenseAssignment
-> Text -> Text -> Text -> LicensingLicenseAssignmentsPatch
newLicensingLicenseAssignmentsPatch LicenseAssignment
payload Text
productId Text
skuId Text
userId =
LicensingLicenseAssignmentsPatch
{ 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,
payload :: LicenseAssignment
payload = LicenseAssignment
payload,
productId :: Text
productId = Text
productId,
skuId :: Text
skuId = Text
skuId,
uploadType :: Maybe Text
uploadType = Maybe Text
forall a. Maybe a
Core.Nothing,
uploadProtocol :: Maybe Text
uploadProtocol = Maybe Text
forall a. Maybe a
Core.Nothing,
userId :: Text
userId = Text
userId
}
instance Core.GoogleRequest LicensingLicenseAssignmentsPatch where
type Rs LicensingLicenseAssignmentsPatch = LicenseAssignment
type Scopes LicensingLicenseAssignmentsPatch = '[Apps'Licensing]
requestClient :: LicensingLicenseAssignmentsPatch
-> GClient (Rs LicensingLicenseAssignmentsPatch)
requestClient LicensingLicenseAssignmentsPatch {Maybe Text
Maybe Xgafv
Text
LicenseAssignment
xgafv :: LicensingLicenseAssignmentsPatch -> Maybe Xgafv
accessToken :: LicensingLicenseAssignmentsPatch -> Maybe Text
callback :: LicensingLicenseAssignmentsPatch -> Maybe Text
payload :: LicensingLicenseAssignmentsPatch -> LicenseAssignment
productId :: LicensingLicenseAssignmentsPatch -> Text
skuId :: LicensingLicenseAssignmentsPatch -> Text
uploadType :: LicensingLicenseAssignmentsPatch -> Maybe Text
uploadProtocol :: LicensingLicenseAssignmentsPatch -> Maybe Text
userId :: LicensingLicenseAssignmentsPatch -> Text
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
payload :: LicenseAssignment
productId :: Text
skuId :: Text
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
userId :: Text
..} =
Text
-> Text
-> Text
-> Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AltJSON
-> LicenseAssignment
-> ServiceConfig
-> GClient LicenseAssignment
go
Text
productId
Text
skuId
Text
userId
Maybe Xgafv
xgafv
Maybe Text
accessToken
Maybe Text
callback
Maybe Text
uploadType
Maybe Text
uploadProtocol
(AltJSON -> Maybe AltJSON
forall a. a -> Maybe a
Core.Just AltJSON
Core.AltJSON)
LicenseAssignment
payload
ServiceConfig
appsLicensingService
where
go :: Fn LicensingLicenseAssignmentsPatchResource
go =
Proxy LicensingLicenseAssignmentsPatchResource
-> Request -> Fn LicensingLicenseAssignmentsPatchResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
(Proxy LicensingLicenseAssignmentsPatchResource
forall {k} (t :: k). Proxy t
Core.Proxy :: Core.Proxy LicensingLicenseAssignmentsPatchResource)
Request
forall a. Monoid a => a
Core.mempty