{-# 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.AndroidManagement.Enterprises.Devices.IssueCommand
(
EnterprisesDevicesIssueCommandResource
, enterprisesDevicesIssueCommand
, EnterprisesDevicesIssueCommand
, edicXgafv
, edicUploadProtocol
, edicAccessToken
, edicUploadType
, edicPayload
, edicName
, edicCallback
) where
import Network.Google.AndroidManagement.Types
import Network.Google.Prelude
type EnterprisesDevicesIssueCommandResource =
"v1" :>
CaptureMode "name" "issueCommand" Text :>
QueryParam "$.xgafv" Xgafv :>
QueryParam "upload_protocol" Text :>
QueryParam "access_token" Text :>
QueryParam "uploadType" Text :>
QueryParam "callback" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Command :> Post '[JSON] Operation
data EnterprisesDevicesIssueCommand = EnterprisesDevicesIssueCommand'
{ _edicXgafv :: !(Maybe Xgafv)
, _edicUploadProtocol :: !(Maybe Text)
, _edicAccessToken :: !(Maybe Text)
, _edicUploadType :: !(Maybe Text)
, _edicPayload :: !Command
, _edicName :: !Text
, _edicCallback :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
enterprisesDevicesIssueCommand
:: Command
-> Text
-> EnterprisesDevicesIssueCommand
enterprisesDevicesIssueCommand pEdicPayload_ pEdicName_ =
EnterprisesDevicesIssueCommand'
{ _edicXgafv = Nothing
, _edicUploadProtocol = Nothing
, _edicAccessToken = Nothing
, _edicUploadType = Nothing
, _edicPayload = pEdicPayload_
, _edicName = pEdicName_
, _edicCallback = Nothing
}
edicXgafv :: Lens' EnterprisesDevicesIssueCommand (Maybe Xgafv)
edicXgafv
= lens _edicXgafv (\ s a -> s{_edicXgafv = a})
edicUploadProtocol :: Lens' EnterprisesDevicesIssueCommand (Maybe Text)
edicUploadProtocol
= lens _edicUploadProtocol
(\ s a -> s{_edicUploadProtocol = a})
edicAccessToken :: Lens' EnterprisesDevicesIssueCommand (Maybe Text)
edicAccessToken
= lens _edicAccessToken
(\ s a -> s{_edicAccessToken = a})
edicUploadType :: Lens' EnterprisesDevicesIssueCommand (Maybe Text)
edicUploadType
= lens _edicUploadType
(\ s a -> s{_edicUploadType = a})
edicPayload :: Lens' EnterprisesDevicesIssueCommand Command
edicPayload
= lens _edicPayload (\ s a -> s{_edicPayload = a})
edicName :: Lens' EnterprisesDevicesIssueCommand Text
edicName = lens _edicName (\ s a -> s{_edicName = a})
edicCallback :: Lens' EnterprisesDevicesIssueCommand (Maybe Text)
edicCallback
= lens _edicCallback (\ s a -> s{_edicCallback = a})
instance GoogleRequest EnterprisesDevicesIssueCommand
where
type Rs EnterprisesDevicesIssueCommand = Operation
type Scopes EnterprisesDevicesIssueCommand =
'["https://www.googleapis.com/auth/androidmanagement"]
requestClient EnterprisesDevicesIssueCommand'{..}
= go _edicName _edicXgafv _edicUploadProtocol
_edicAccessToken
_edicUploadType
_edicCallback
(Just AltJSON)
_edicPayload
androidManagementService
where go
= buildClient
(Proxy ::
Proxy EnterprisesDevicesIssueCommandResource)
mempty