{-# 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.Directory.Resources.Features.Patch
(
ResourcesFeaturesPatchResource
, resourcesFeaturesPatch
, ResourcesFeaturesPatch
, rfpPayload
, rfpCustomer
, rfpFeatureKey
) where
import Network.Google.Directory.Types
import Network.Google.Prelude
type ResourcesFeaturesPatchResource =
"admin" :>
"directory" :>
"v1" :>
"customer" :>
Capture "customer" Text :>
"resources" :>
"features" :>
Capture "featureKey" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Feature :> Patch '[JSON] Feature
data ResourcesFeaturesPatch = ResourcesFeaturesPatch'
{ _rfpPayload :: !Feature
, _rfpCustomer :: !Text
, _rfpFeatureKey :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
resourcesFeaturesPatch
:: Feature
-> Text
-> Text
-> ResourcesFeaturesPatch
resourcesFeaturesPatch pRfpPayload_ pRfpCustomer_ pRfpFeatureKey_ =
ResourcesFeaturesPatch'
{ _rfpPayload = pRfpPayload_
, _rfpCustomer = pRfpCustomer_
, _rfpFeatureKey = pRfpFeatureKey_
}
rfpPayload :: Lens' ResourcesFeaturesPatch Feature
rfpPayload
= lens _rfpPayload (\ s a -> s{_rfpPayload = a})
rfpCustomer :: Lens' ResourcesFeaturesPatch Text
rfpCustomer
= lens _rfpCustomer (\ s a -> s{_rfpCustomer = a})
rfpFeatureKey :: Lens' ResourcesFeaturesPatch Text
rfpFeatureKey
= lens _rfpFeatureKey
(\ s a -> s{_rfpFeatureKey = a})
instance GoogleRequest ResourcesFeaturesPatch where
type Rs ResourcesFeaturesPatch = Feature
type Scopes ResourcesFeaturesPatch =
'["https://www.googleapis.com/auth/admin.directory.resource.calendar"]
requestClient ResourcesFeaturesPatch'{..}
= go _rfpCustomer _rfpFeatureKey (Just AltJSON)
_rfpPayload
directoryService
where go
= buildClient
(Proxy :: Proxy ResourcesFeaturesPatchResource)
mempty