{-# 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.OrgUnits.Patch
(
OrgUnitsPatchResource
, orgUnitsPatch
, OrgUnitsPatch
, oupPayload
, oupOrgUnitPath
, oupCustomerId
) where
import Network.Google.Directory.Types
import Network.Google.Prelude
type OrgUnitsPatchResource =
"admin" :>
"directory" :>
"v1" :>
"customer" :>
Capture "customerId" Text :>
"orgunits" :>
Captures "orgUnitPath" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] OrgUnit :> Patch '[JSON] OrgUnit
data OrgUnitsPatch = OrgUnitsPatch'
{ _oupPayload :: !OrgUnit
, _oupOrgUnitPath :: ![Text]
, _oupCustomerId :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
orgUnitsPatch
:: OrgUnit
-> [Text]
-> Text
-> OrgUnitsPatch
orgUnitsPatch pOupPayload_ pOupOrgUnitPath_ pOupCustomerId_ =
OrgUnitsPatch'
{ _oupPayload = pOupPayload_
, _oupOrgUnitPath = _Coerce # pOupOrgUnitPath_
, _oupCustomerId = pOupCustomerId_
}
oupPayload :: Lens' OrgUnitsPatch OrgUnit
oupPayload
= lens _oupPayload (\ s a -> s{_oupPayload = a})
oupOrgUnitPath :: Lens' OrgUnitsPatch [Text]
oupOrgUnitPath
= lens _oupOrgUnitPath
(\ s a -> s{_oupOrgUnitPath = a})
. _Coerce
oupCustomerId :: Lens' OrgUnitsPatch Text
oupCustomerId
= lens _oupCustomerId
(\ s a -> s{_oupCustomerId = a})
instance GoogleRequest OrgUnitsPatch where
type Rs OrgUnitsPatch = OrgUnit
type Scopes OrgUnitsPatch =
'["https://www.googleapis.com/auth/admin.directory.orgunit"]
requestClient OrgUnitsPatch'{..}
= go _oupCustomerId _oupOrgUnitPath (Just AltJSON)
_oupPayload
directoryService
where go
= buildClient (Proxy :: Proxy OrgUnitsPatchResource)
mempty