{-# 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.Storage.ObjectAccessControls.Insert
(
ObjectAccessControlsInsertResource
, objectAccessControlsInsert
, ObjectAccessControlsInsert
, oaciBucket
, oaciPayload
, oaciUserProject
, oaciObject
, oaciGeneration
) where
import Network.Google.Prelude
import Network.Google.Storage.Types
type ObjectAccessControlsInsertResource =
"storage" :>
"v1" :>
"b" :>
Capture "bucket" Text :>
"o" :>
Capture "object" Text :>
"acl" :>
QueryParam "userProject" Text :>
QueryParam "generation" (Textual Int64) :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] ObjectAccessControl :>
Post '[JSON] ObjectAccessControl
data ObjectAccessControlsInsert = ObjectAccessControlsInsert'
{ _oaciBucket :: !Text
, _oaciPayload :: !ObjectAccessControl
, _oaciUserProject :: !(Maybe Text)
, _oaciObject :: !Text
, _oaciGeneration :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
objectAccessControlsInsert
:: Text
-> ObjectAccessControl
-> Text
-> ObjectAccessControlsInsert
objectAccessControlsInsert pOaciBucket_ pOaciPayload_ pOaciObject_ =
ObjectAccessControlsInsert'
{ _oaciBucket = pOaciBucket_
, _oaciPayload = pOaciPayload_
, _oaciUserProject = Nothing
, _oaciObject = pOaciObject_
, _oaciGeneration = Nothing
}
oaciBucket :: Lens' ObjectAccessControlsInsert Text
oaciBucket
= lens _oaciBucket (\ s a -> s{_oaciBucket = a})
oaciPayload :: Lens' ObjectAccessControlsInsert ObjectAccessControl
oaciPayload
= lens _oaciPayload (\ s a -> s{_oaciPayload = a})
oaciUserProject :: Lens' ObjectAccessControlsInsert (Maybe Text)
oaciUserProject
= lens _oaciUserProject
(\ s a -> s{_oaciUserProject = a})
oaciObject :: Lens' ObjectAccessControlsInsert Text
oaciObject
= lens _oaciObject (\ s a -> s{_oaciObject = a})
oaciGeneration :: Lens' ObjectAccessControlsInsert (Maybe Int64)
oaciGeneration
= lens _oaciGeneration
(\ s a -> s{_oaciGeneration = a})
. mapping _Coerce
instance GoogleRequest ObjectAccessControlsInsert
where
type Rs ObjectAccessControlsInsert =
ObjectAccessControl
type Scopes ObjectAccessControlsInsert =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/devstorage.full_control"]
requestClient ObjectAccessControlsInsert'{..}
= go _oaciBucket _oaciObject _oaciUserProject
_oaciGeneration
(Just AltJSON)
_oaciPayload
storageService
where go
= buildClient
(Proxy :: Proxy ObjectAccessControlsInsertResource)
mempty