{-# 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.Objects.Rewrite
(
ObjectsRewriteResource
, objectsRewrite
, ObjectsRewrite
, orDestinationPredefinedACL
, orIfSourceGenerationMatch
, orIfMetagenerationMatch
, orIfGenerationNotMatch
, orIfSourceMetagenerationNotMatch
, orIfSourceMetagenerationMatch
, orIfGenerationMatch
, orSourceObject
, orMaxBytesRewrittenPerCall
, orSourceBucket
, orPayload
, orUserProject
, orDestinationBucket
, orIfMetagenerationNotMatch
, orIfSourceGenerationNotMatch
, orProjection
, orSourceGeneration
, orDestinationKmsKeyName
, orRewriteToken
, orDestinationObject
) where
import Network.Google.Prelude
import Network.Google.Storage.Types
type ObjectsRewriteResource =
"storage" :>
"v1" :>
"b" :>
Capture "sourceBucket" Text :>
"o" :>
Capture "sourceObject" Text :>
"rewriteTo" :>
"b" :>
Capture "destinationBucket" Text :>
"o" :>
Capture "destinationObject" Text :>
QueryParam "destinationPredefinedAcl"
ObjectsRewriteDestinationPredefinedACL
:>
QueryParam "ifSourceGenerationMatch"
(Textual Int64)
:>
QueryParam "ifMetagenerationMatch"
(Textual Int64)
:>
QueryParam "ifGenerationNotMatch"
(Textual Int64)
:>
QueryParam "ifSourceMetagenerationNotMatch"
(Textual Int64)
:>
QueryParam "ifSourceMetagenerationMatch"
(Textual Int64)
:>
QueryParam "ifGenerationMatch"
(Textual Int64)
:>
QueryParam "maxBytesRewrittenPerCall"
(Textual Int64)
:>
QueryParam "userProject" Text :>
QueryParam
"ifMetagenerationNotMatch"
(Textual Int64)
:>
QueryParam
"ifSourceGenerationNotMatch"
(Textual Int64)
:>
QueryParam "projection"
ObjectsRewriteProjection
:>
QueryParam "sourceGeneration"
(Textual Int64)
:>
QueryParam
"destinationKmsKeyName"
Text
:>
QueryParam "rewriteToken"
Text
:>
QueryParam "alt"
AltJSON
:>
ReqBody '[JSON]
Object
:>
Post '[JSON]
RewriteResponse
data ObjectsRewrite =
ObjectsRewrite'
{ _orDestinationPredefinedACL :: !(Maybe ObjectsRewriteDestinationPredefinedACL)
, _orIfSourceGenerationMatch :: !(Maybe (Textual Int64))
, _orIfMetagenerationMatch :: !(Maybe (Textual Int64))
, _orIfGenerationNotMatch :: !(Maybe (Textual Int64))
, _orIfSourceMetagenerationNotMatch :: !(Maybe (Textual Int64))
, _orIfSourceMetagenerationMatch :: !(Maybe (Textual Int64))
, _orIfGenerationMatch :: !(Maybe (Textual Int64))
, _orSourceObject :: !Text
, _orMaxBytesRewrittenPerCall :: !(Maybe (Textual Int64))
, _orSourceBucket :: !Text
, _orPayload :: !Object
, _orUserProject :: !(Maybe Text)
, _orDestinationBucket :: !Text
, _orIfMetagenerationNotMatch :: !(Maybe (Textual Int64))
, _orIfSourceGenerationNotMatch :: !(Maybe (Textual Int64))
, _orProjection :: !(Maybe ObjectsRewriteProjection)
, _orSourceGeneration :: !(Maybe (Textual Int64))
, _orDestinationKmsKeyName :: !(Maybe Text)
, _orRewriteToken :: !(Maybe Text)
, _orDestinationObject :: !Text
}
deriving (Eq, Show, Data, Typeable, Generic)
objectsRewrite
:: Text
-> Text
-> Object
-> Text
-> Text
-> ObjectsRewrite
objectsRewrite pOrSourceObject_ pOrSourceBucket_ pOrPayload_ pOrDestinationBucket_ pOrDestinationObject_ =
ObjectsRewrite'
{ _orDestinationPredefinedACL = Nothing
, _orIfSourceGenerationMatch = Nothing
, _orIfMetagenerationMatch = Nothing
, _orIfGenerationNotMatch = Nothing
, _orIfSourceMetagenerationNotMatch = Nothing
, _orIfSourceMetagenerationMatch = Nothing
, _orIfGenerationMatch = Nothing
, _orSourceObject = pOrSourceObject_
, _orMaxBytesRewrittenPerCall = Nothing
, _orSourceBucket = pOrSourceBucket_
, _orPayload = pOrPayload_
, _orUserProject = Nothing
, _orDestinationBucket = pOrDestinationBucket_
, _orIfMetagenerationNotMatch = Nothing
, _orIfSourceGenerationNotMatch = Nothing
, _orProjection = Nothing
, _orSourceGeneration = Nothing
, _orDestinationKmsKeyName = Nothing
, _orRewriteToken = Nothing
, _orDestinationObject = pOrDestinationObject_
}
orDestinationPredefinedACL :: Lens' ObjectsRewrite (Maybe ObjectsRewriteDestinationPredefinedACL)
orDestinationPredefinedACL
= lens _orDestinationPredefinedACL
(\ s a -> s{_orDestinationPredefinedACL = a})
orIfSourceGenerationMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfSourceGenerationMatch
= lens _orIfSourceGenerationMatch
(\ s a -> s{_orIfSourceGenerationMatch = a})
. mapping _Coerce
orIfMetagenerationMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfMetagenerationMatch
= lens _orIfMetagenerationMatch
(\ s a -> s{_orIfMetagenerationMatch = a})
. mapping _Coerce
orIfGenerationNotMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfGenerationNotMatch
= lens _orIfGenerationNotMatch
(\ s a -> s{_orIfGenerationNotMatch = a})
. mapping _Coerce
orIfSourceMetagenerationNotMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfSourceMetagenerationNotMatch
= lens _orIfSourceMetagenerationNotMatch
(\ s a -> s{_orIfSourceMetagenerationNotMatch = a})
. mapping _Coerce
orIfSourceMetagenerationMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfSourceMetagenerationMatch
= lens _orIfSourceMetagenerationMatch
(\ s a -> s{_orIfSourceMetagenerationMatch = a})
. mapping _Coerce
orIfGenerationMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfGenerationMatch
= lens _orIfGenerationMatch
(\ s a -> s{_orIfGenerationMatch = a})
. mapping _Coerce
orSourceObject :: Lens' ObjectsRewrite Text
orSourceObject
= lens _orSourceObject
(\ s a -> s{_orSourceObject = a})
orMaxBytesRewrittenPerCall :: Lens' ObjectsRewrite (Maybe Int64)
orMaxBytesRewrittenPerCall
= lens _orMaxBytesRewrittenPerCall
(\ s a -> s{_orMaxBytesRewrittenPerCall = a})
. mapping _Coerce
orSourceBucket :: Lens' ObjectsRewrite Text
orSourceBucket
= lens _orSourceBucket
(\ s a -> s{_orSourceBucket = a})
orPayload :: Lens' ObjectsRewrite Object
orPayload
= lens _orPayload (\ s a -> s{_orPayload = a})
orUserProject :: Lens' ObjectsRewrite (Maybe Text)
orUserProject
= lens _orUserProject
(\ s a -> s{_orUserProject = a})
orDestinationBucket :: Lens' ObjectsRewrite Text
orDestinationBucket
= lens _orDestinationBucket
(\ s a -> s{_orDestinationBucket = a})
orIfMetagenerationNotMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfMetagenerationNotMatch
= lens _orIfMetagenerationNotMatch
(\ s a -> s{_orIfMetagenerationNotMatch = a})
. mapping _Coerce
orIfSourceGenerationNotMatch :: Lens' ObjectsRewrite (Maybe Int64)
orIfSourceGenerationNotMatch
= lens _orIfSourceGenerationNotMatch
(\ s a -> s{_orIfSourceGenerationNotMatch = a})
. mapping _Coerce
orProjection :: Lens' ObjectsRewrite (Maybe ObjectsRewriteProjection)
orProjection
= lens _orProjection (\ s a -> s{_orProjection = a})
orSourceGeneration :: Lens' ObjectsRewrite (Maybe Int64)
orSourceGeneration
= lens _orSourceGeneration
(\ s a -> s{_orSourceGeneration = a})
. mapping _Coerce
orDestinationKmsKeyName :: Lens' ObjectsRewrite (Maybe Text)
orDestinationKmsKeyName
= lens _orDestinationKmsKeyName
(\ s a -> s{_orDestinationKmsKeyName = a})
orRewriteToken :: Lens' ObjectsRewrite (Maybe Text)
orRewriteToken
= lens _orRewriteToken
(\ s a -> s{_orRewriteToken = a})
orDestinationObject :: Lens' ObjectsRewrite Text
orDestinationObject
= lens _orDestinationObject
(\ s a -> s{_orDestinationObject = a})
instance GoogleRequest ObjectsRewrite where
type Rs ObjectsRewrite = RewriteResponse
type Scopes ObjectsRewrite =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/devstorage.full_control",
"https://www.googleapis.com/auth/devstorage.read_write"]
requestClient ObjectsRewrite'{..}
= go _orSourceBucket _orSourceObject
_orDestinationBucket
_orDestinationObject
_orDestinationPredefinedACL
_orIfSourceGenerationMatch
_orIfMetagenerationMatch
_orIfGenerationNotMatch
_orIfSourceMetagenerationNotMatch
_orIfSourceMetagenerationMatch
_orIfGenerationMatch
_orMaxBytesRewrittenPerCall
_orUserProject
_orIfMetagenerationNotMatch
_orIfSourceGenerationNotMatch
_orProjection
_orSourceGeneration
_orDestinationKmsKeyName
_orRewriteToken
(Just AltJSON)
_orPayload
storageService
where go
= buildClient (Proxy :: Proxy ObjectsRewriteResource)
mempty