{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Resource.PlayCustomApp.Accounts.CustomApps.Create
(
AccountsCustomAppsCreateResource
, accountsCustomAppsCreate
, AccountsCustomAppsCreate
, acacPayload
, acacAccount
) where
import Network.Google.PlayCustomApp.Types
import Network.Google.Prelude
type AccountsCustomAppsCreateResource =
"playcustomapp" :>
"v1" :>
"accounts" :>
Capture "account" (Textual Int64) :>
"customApps" :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] CustomApp :> Post '[JSON] CustomApp
:<|>
"upload" :>
"playcustomapp" :>
"v1" :>
"accounts" :>
Capture "account" (Textual Int64) :>
"customApps" :>
QueryParam "alt" AltJSON :>
QueryParam "uploadType" Multipart :>
MultipartRelated '[JSON] CustomApp :>
Post '[JSON] CustomApp
data AccountsCustomAppsCreate = AccountsCustomAppsCreate'
{ _acacPayload :: !CustomApp
, _acacAccount :: !(Textual Int64)
} deriving (Eq,Show,Data,Typeable,Generic)
accountsCustomAppsCreate
:: CustomApp
-> Int64
-> AccountsCustomAppsCreate
accountsCustomAppsCreate pAcacPayload_ pAcacAccount_ =
AccountsCustomAppsCreate'
{ _acacPayload = pAcacPayload_
, _acacAccount = _Coerce # pAcacAccount_
}
acacPayload :: Lens' AccountsCustomAppsCreate CustomApp
acacPayload
= lens _acacPayload (\ s a -> s{_acacPayload = a})
acacAccount :: Lens' AccountsCustomAppsCreate Int64
acacAccount
= lens _acacAccount (\ s a -> s{_acacAccount = a}) .
_Coerce
instance GoogleRequest AccountsCustomAppsCreate where
type Rs AccountsCustomAppsCreate = CustomApp
type Scopes AccountsCustomAppsCreate =
'["https://www.googleapis.com/auth/androidpublisher"]
requestClient AccountsCustomAppsCreate'{..}
= go _acacAccount (Just AltJSON) _acacPayload
playCustomAppService
where go :<|> _
= buildClient
(Proxy :: Proxy AccountsCustomAppsCreateResource)
mempty
instance GoogleRequest
(MediaUpload AccountsCustomAppsCreate) where
type Rs (MediaUpload AccountsCustomAppsCreate) =
CustomApp
type Scopes (MediaUpload AccountsCustomAppsCreate) =
Scopes AccountsCustomAppsCreate
requestClient
(MediaUpload AccountsCustomAppsCreate'{..} body)
= go _acacAccount (Just AltJSON) (Just Multipart)
_acacPayload
body
playCustomAppService
where _ :<|> go
= buildClient
(Proxy :: Proxy AccountsCustomAppsCreateResource)
mempty