{-# 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.Compute.Instances.StartWithEncryptionKey
(
InstancesStartWithEncryptionKeyResource
, instancesStartWithEncryptionKey
, InstancesStartWithEncryptionKey
, iswekRequestId
, iswekProject
, iswekZone
, iswekPayload
, iswekInstance
) where
import Network.Google.Compute.Types
import Network.Google.Prelude
type InstancesStartWithEncryptionKeyResource =
"compute" :>
"v1" :>
"projects" :>
Capture "project" Text :>
"zones" :>
Capture "zone" Text :>
"instances" :>
Capture "instance" Text :>
"startWithEncryptionKey" :>
QueryParam "requestId" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON]
InstancesStartWithEncryptionKeyRequest
:> Post '[JSON] Operation
data InstancesStartWithEncryptionKey = InstancesStartWithEncryptionKey'
{ _iswekRequestId :: !(Maybe Text)
, _iswekProject :: !Text
, _iswekZone :: !Text
, _iswekPayload :: !InstancesStartWithEncryptionKeyRequest
, _iswekInstance :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
instancesStartWithEncryptionKey
:: Text
-> Text
-> InstancesStartWithEncryptionKeyRequest
-> Text
-> InstancesStartWithEncryptionKey
instancesStartWithEncryptionKey pIswekProject_ pIswekZone_ pIswekPayload_ pIswekInstance_ =
InstancesStartWithEncryptionKey'
{ _iswekRequestId = Nothing
, _iswekProject = pIswekProject_
, _iswekZone = pIswekZone_
, _iswekPayload = pIswekPayload_
, _iswekInstance = pIswekInstance_
}
iswekRequestId :: Lens' InstancesStartWithEncryptionKey (Maybe Text)
iswekRequestId
= lens _iswekRequestId
(\ s a -> s{_iswekRequestId = a})
iswekProject :: Lens' InstancesStartWithEncryptionKey Text
iswekProject
= lens _iswekProject (\ s a -> s{_iswekProject = a})
iswekZone :: Lens' InstancesStartWithEncryptionKey Text
iswekZone
= lens _iswekZone (\ s a -> s{_iswekZone = a})
iswekPayload :: Lens' InstancesStartWithEncryptionKey InstancesStartWithEncryptionKeyRequest
iswekPayload
= lens _iswekPayload (\ s a -> s{_iswekPayload = a})
iswekInstance :: Lens' InstancesStartWithEncryptionKey Text
iswekInstance
= lens _iswekInstance
(\ s a -> s{_iswekInstance = a})
instance GoogleRequest
InstancesStartWithEncryptionKey where
type Rs InstancesStartWithEncryptionKey = Operation
type Scopes InstancesStartWithEncryptionKey =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/compute"]
requestClient InstancesStartWithEncryptionKey'{..}
= go _iswekProject _iswekZone _iswekInstance
_iswekRequestId
(Just AltJSON)
_iswekPayload
computeService
where go
= buildClient
(Proxy ::
Proxy InstancesStartWithEncryptionKeyResource)
mempty