{-# 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.TargetPools.SetBackup
(
TargetPoolsSetBackupResource
, targetPoolsSetBackup
, TargetPoolsSetBackup
, tpsbRequestId
, tpsbProject
, tpsbTargetPool
, tpsbPayload
, tpsbFailoverRatio
, tpsbRegion
) where
import Network.Google.Compute.Types
import Network.Google.Prelude
type TargetPoolsSetBackupResource =
"compute" :>
"v1" :>
"projects" :>
Capture "project" Text :>
"regions" :>
Capture "region" Text :>
"targetPools" :>
Capture "targetPool" Text :>
"setBackup" :>
QueryParam "requestId" Text :>
QueryParam "failoverRatio" (Textual Double) :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] TargetReference :>
Post '[JSON] Operation
data TargetPoolsSetBackup = TargetPoolsSetBackup'
{ _tpsbRequestId :: !(Maybe Text)
, _tpsbProject :: !Text
, _tpsbTargetPool :: !Text
, _tpsbPayload :: !TargetReference
, _tpsbFailoverRatio :: !(Maybe (Textual Double))
, _tpsbRegion :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
targetPoolsSetBackup
:: Text
-> Text
-> TargetReference
-> Text
-> TargetPoolsSetBackup
targetPoolsSetBackup pTpsbProject_ pTpsbTargetPool_ pTpsbPayload_ pTpsbRegion_ =
TargetPoolsSetBackup'
{ _tpsbRequestId = Nothing
, _tpsbProject = pTpsbProject_
, _tpsbTargetPool = pTpsbTargetPool_
, _tpsbPayload = pTpsbPayload_
, _tpsbFailoverRatio = Nothing
, _tpsbRegion = pTpsbRegion_
}
tpsbRequestId :: Lens' TargetPoolsSetBackup (Maybe Text)
tpsbRequestId
= lens _tpsbRequestId
(\ s a -> s{_tpsbRequestId = a})
tpsbProject :: Lens' TargetPoolsSetBackup Text
tpsbProject
= lens _tpsbProject (\ s a -> s{_tpsbProject = a})
tpsbTargetPool :: Lens' TargetPoolsSetBackup Text
tpsbTargetPool
= lens _tpsbTargetPool
(\ s a -> s{_tpsbTargetPool = a})
tpsbPayload :: Lens' TargetPoolsSetBackup TargetReference
tpsbPayload
= lens _tpsbPayload (\ s a -> s{_tpsbPayload = a})
tpsbFailoverRatio :: Lens' TargetPoolsSetBackup (Maybe Double)
tpsbFailoverRatio
= lens _tpsbFailoverRatio
(\ s a -> s{_tpsbFailoverRatio = a})
. mapping _Coerce
tpsbRegion :: Lens' TargetPoolsSetBackup Text
tpsbRegion
= lens _tpsbRegion (\ s a -> s{_tpsbRegion = a})
instance GoogleRequest TargetPoolsSetBackup where
type Rs TargetPoolsSetBackup = Operation
type Scopes TargetPoolsSetBackup =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/compute"]
requestClient TargetPoolsSetBackup'{..}
= go _tpsbProject _tpsbRegion _tpsbTargetPool
_tpsbRequestId
_tpsbFailoverRatio
(Just AltJSON)
_tpsbPayload
computeService
where go
= buildClient
(Proxy :: Proxy TargetPoolsSetBackupResource)
mempty