{-# 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.TargetSSLProxies.SetSSLPolicy
(
TargetSSLProxiesSetSSLPolicyResource
, targetSSLProxiesSetSSLPolicy
, TargetSSLProxiesSetSSLPolicy
, tspsspRequestId
, tspsspProject
, tspsspPayload
, tspsspTargetSSLProxy
) where
import Network.Google.Compute.Types
import Network.Google.Prelude
type TargetSSLProxiesSetSSLPolicyResource =
"compute" :>
"v1" :>
"projects" :>
Capture "project" Text :>
"global" :>
"targetSslProxies" :>
Capture "targetSslProxy" Text :>
"setSslPolicy" :>
QueryParam "requestId" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] SSLPolicyReference :>
Post '[JSON] Operation
data TargetSSLProxiesSetSSLPolicy = TargetSSLProxiesSetSSLPolicy'
{ _tspsspRequestId :: !(Maybe Text)
, _tspsspProject :: !Text
, _tspsspPayload :: !SSLPolicyReference
, _tspsspTargetSSLProxy :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
targetSSLProxiesSetSSLPolicy
:: Text
-> SSLPolicyReference
-> Text
-> TargetSSLProxiesSetSSLPolicy
targetSSLProxiesSetSSLPolicy pTspsspProject_ pTspsspPayload_ pTspsspTargetSSLProxy_ =
TargetSSLProxiesSetSSLPolicy'
{ _tspsspRequestId = Nothing
, _tspsspProject = pTspsspProject_
, _tspsspPayload = pTspsspPayload_
, _tspsspTargetSSLProxy = pTspsspTargetSSLProxy_
}
tspsspRequestId :: Lens' TargetSSLProxiesSetSSLPolicy (Maybe Text)
tspsspRequestId
= lens _tspsspRequestId
(\ s a -> s{_tspsspRequestId = a})
tspsspProject :: Lens' TargetSSLProxiesSetSSLPolicy Text
tspsspProject
= lens _tspsspProject
(\ s a -> s{_tspsspProject = a})
tspsspPayload :: Lens' TargetSSLProxiesSetSSLPolicy SSLPolicyReference
tspsspPayload
= lens _tspsspPayload
(\ s a -> s{_tspsspPayload = a})
tspsspTargetSSLProxy :: Lens' TargetSSLProxiesSetSSLPolicy Text
tspsspTargetSSLProxy
= lens _tspsspTargetSSLProxy
(\ s a -> s{_tspsspTargetSSLProxy = a})
instance GoogleRequest TargetSSLProxiesSetSSLPolicy
where
type Rs TargetSSLProxiesSetSSLPolicy = Operation
type Scopes TargetSSLProxiesSetSSLPolicy =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/compute"]
requestClient TargetSSLProxiesSetSSLPolicy'{..}
= go _tspsspProject _tspsspTargetSSLProxy
_tspsspRequestId
(Just AltJSON)
_tspsspPayload
computeService
where go
= buildClient
(Proxy :: Proxy TargetSSLProxiesSetSSLPolicyResource)
mempty