{-# 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.TargetHTTPSProxies.Insert
(
TargetHTTPSProxiesInsertResource
, targetHTTPSProxiesInsert
, TargetHTTPSProxiesInsert
, thpiRequestId
, thpiProject
, thpiPayload
) where
import Network.Google.Compute.Types
import Network.Google.Prelude
type TargetHTTPSProxiesInsertResource =
"compute" :>
"v1" :>
"projects" :>
Capture "project" Text :>
"global" :>
"targetHttpsProxies" :>
QueryParam "requestId" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] TargetHTTPSProxy :>
Post '[JSON] Operation
data TargetHTTPSProxiesInsert = TargetHTTPSProxiesInsert'
{ _thpiRequestId :: !(Maybe Text)
, _thpiProject :: !Text
, _thpiPayload :: !TargetHTTPSProxy
} deriving (Eq,Show,Data,Typeable,Generic)
targetHTTPSProxiesInsert
:: Text
-> TargetHTTPSProxy
-> TargetHTTPSProxiesInsert
targetHTTPSProxiesInsert pThpiProject_ pThpiPayload_ =
TargetHTTPSProxiesInsert'
{ _thpiRequestId = Nothing
, _thpiProject = pThpiProject_
, _thpiPayload = pThpiPayload_
}
thpiRequestId :: Lens' TargetHTTPSProxiesInsert (Maybe Text)
thpiRequestId
= lens _thpiRequestId
(\ s a -> s{_thpiRequestId = a})
thpiProject :: Lens' TargetHTTPSProxiesInsert Text
thpiProject
= lens _thpiProject (\ s a -> s{_thpiProject = a})
thpiPayload :: Lens' TargetHTTPSProxiesInsert TargetHTTPSProxy
thpiPayload
= lens _thpiPayload (\ s a -> s{_thpiPayload = a})
instance GoogleRequest TargetHTTPSProxiesInsert where
type Rs TargetHTTPSProxiesInsert = Operation
type Scopes TargetHTTPSProxiesInsert =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/compute"]
requestClient TargetHTTPSProxiesInsert'{..}
= go _thpiProject _thpiRequestId (Just AltJSON)
_thpiPayload
computeService
where go
= buildClient
(Proxy :: Proxy TargetHTTPSProxiesInsertResource)
mempty