{-# 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.Copy
(
ObjectsCopyResource
, objectsCopy
, ObjectsCopy
, ocDestinationPredefinedACL
, ocIfSourceGenerationMatch
, ocIfMetagenerationMatch
, ocIfGenerationNotMatch
, ocIfSourceMetagenerationNotMatch
, ocIfSourceMetagenerationMatch
, ocIfGenerationMatch
, ocSourceObject
, ocSourceBucket
, ocPayload
, ocUserProject
, ocDestinationBucket
, ocIfMetagenerationNotMatch
, ocIfSourceGenerationNotMatch
, ocProjection
, ocSourceGeneration
, ocDestinationObject
) where
import Network.Google.Prelude
import Network.Google.Storage.Types
type ObjectsCopyResource =
"storage" :>
"v1" :>
"b" :>
Capture "sourceBucket" Text :>
"o" :>
Capture "sourceObject" Text :>
"copyTo" :>
"b" :>
Capture "destinationBucket" Text :>
"o" :>
Capture "destinationObject" Text :>
QueryParam "destinationPredefinedAcl"
ObjectsCopyDestinationPredefinedACL
:>
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 "userProject" Text :>
QueryParam "ifMetagenerationNotMatch"
(Textual Int64)
:>
QueryParam
"ifSourceGenerationNotMatch"
(Textual Int64)
:>
QueryParam "projection"
ObjectsCopyProjection
:>
QueryParam "sourceGeneration"
(Textual Int64)
:>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Object :>
Post '[JSON] Object
data ObjectsCopy = ObjectsCopy'
{ _ocDestinationPredefinedACL :: !(Maybe ObjectsCopyDestinationPredefinedACL)
, _ocIfSourceGenerationMatch :: !(Maybe (Textual Int64))
, _ocIfMetagenerationMatch :: !(Maybe (Textual Int64))
, _ocIfGenerationNotMatch :: !(Maybe (Textual Int64))
, _ocIfSourceMetagenerationNotMatch :: !(Maybe (Textual Int64))
, _ocIfSourceMetagenerationMatch :: !(Maybe (Textual Int64))
, _ocIfGenerationMatch :: !(Maybe (Textual Int64))
, _ocSourceObject :: !Text
, _ocSourceBucket :: !Text
, _ocPayload :: !Object
, _ocUserProject :: !(Maybe Text)
, _ocDestinationBucket :: !Text
, _ocIfMetagenerationNotMatch :: !(Maybe (Textual Int64))
, _ocIfSourceGenerationNotMatch :: !(Maybe (Textual Int64))
, _ocProjection :: !(Maybe ObjectsCopyProjection)
, _ocSourceGeneration :: !(Maybe (Textual Int64))
, _ocDestinationObject :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
objectsCopy
:: Text
-> Text
-> Object
-> Text
-> Text
-> ObjectsCopy
objectsCopy pOcSourceObject_ pOcSourceBucket_ pOcPayload_ pOcDestinationBucket_ pOcDestinationObject_ =
ObjectsCopy'
{ _ocDestinationPredefinedACL = Nothing
, _ocIfSourceGenerationMatch = Nothing
, _ocIfMetagenerationMatch = Nothing
, _ocIfGenerationNotMatch = Nothing
, _ocIfSourceMetagenerationNotMatch = Nothing
, _ocIfSourceMetagenerationMatch = Nothing
, _ocIfGenerationMatch = Nothing
, _ocSourceObject = pOcSourceObject_
, _ocSourceBucket = pOcSourceBucket_
, _ocPayload = pOcPayload_
, _ocUserProject = Nothing
, _ocDestinationBucket = pOcDestinationBucket_
, _ocIfMetagenerationNotMatch = Nothing
, _ocIfSourceGenerationNotMatch = Nothing
, _ocProjection = Nothing
, _ocSourceGeneration = Nothing
, _ocDestinationObject = pOcDestinationObject_
}
ocDestinationPredefinedACL :: Lens' ObjectsCopy (Maybe ObjectsCopyDestinationPredefinedACL)
ocDestinationPredefinedACL
= lens _ocDestinationPredefinedACL
(\ s a -> s{_ocDestinationPredefinedACL = a})
ocIfSourceGenerationMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfSourceGenerationMatch
= lens _ocIfSourceGenerationMatch
(\ s a -> s{_ocIfSourceGenerationMatch = a})
. mapping _Coerce
ocIfMetagenerationMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfMetagenerationMatch
= lens _ocIfMetagenerationMatch
(\ s a -> s{_ocIfMetagenerationMatch = a})
. mapping _Coerce
ocIfGenerationNotMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfGenerationNotMatch
= lens _ocIfGenerationNotMatch
(\ s a -> s{_ocIfGenerationNotMatch = a})
. mapping _Coerce
ocIfSourceMetagenerationNotMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfSourceMetagenerationNotMatch
= lens _ocIfSourceMetagenerationNotMatch
(\ s a -> s{_ocIfSourceMetagenerationNotMatch = a})
. mapping _Coerce
ocIfSourceMetagenerationMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfSourceMetagenerationMatch
= lens _ocIfSourceMetagenerationMatch
(\ s a -> s{_ocIfSourceMetagenerationMatch = a})
. mapping _Coerce
ocIfGenerationMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfGenerationMatch
= lens _ocIfGenerationMatch
(\ s a -> s{_ocIfGenerationMatch = a})
. mapping _Coerce
ocSourceObject :: Lens' ObjectsCopy Text
ocSourceObject
= lens _ocSourceObject
(\ s a -> s{_ocSourceObject = a})
ocSourceBucket :: Lens' ObjectsCopy Text
ocSourceBucket
= lens _ocSourceBucket
(\ s a -> s{_ocSourceBucket = a})
ocPayload :: Lens' ObjectsCopy Object
ocPayload
= lens _ocPayload (\ s a -> s{_ocPayload = a})
ocUserProject :: Lens' ObjectsCopy (Maybe Text)
ocUserProject
= lens _ocUserProject
(\ s a -> s{_ocUserProject = a})
ocDestinationBucket :: Lens' ObjectsCopy Text
ocDestinationBucket
= lens _ocDestinationBucket
(\ s a -> s{_ocDestinationBucket = a})
ocIfMetagenerationNotMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfMetagenerationNotMatch
= lens _ocIfMetagenerationNotMatch
(\ s a -> s{_ocIfMetagenerationNotMatch = a})
. mapping _Coerce
ocIfSourceGenerationNotMatch :: Lens' ObjectsCopy (Maybe Int64)
ocIfSourceGenerationNotMatch
= lens _ocIfSourceGenerationNotMatch
(\ s a -> s{_ocIfSourceGenerationNotMatch = a})
. mapping _Coerce
ocProjection :: Lens' ObjectsCopy (Maybe ObjectsCopyProjection)
ocProjection
= lens _ocProjection (\ s a -> s{_ocProjection = a})
ocSourceGeneration :: Lens' ObjectsCopy (Maybe Int64)
ocSourceGeneration
= lens _ocSourceGeneration
(\ s a -> s{_ocSourceGeneration = a})
. mapping _Coerce
ocDestinationObject :: Lens' ObjectsCopy Text
ocDestinationObject
= lens _ocDestinationObject
(\ s a -> s{_ocDestinationObject = a})
instance GoogleRequest ObjectsCopy where
type Rs ObjectsCopy = Object
type Scopes ObjectsCopy =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/devstorage.full_control",
"https://www.googleapis.com/auth/devstorage.read_write"]
requestClient ObjectsCopy'{..}
= go _ocSourceBucket _ocSourceObject
_ocDestinationBucket
_ocDestinationObject
_ocDestinationPredefinedACL
_ocIfSourceGenerationMatch
_ocIfMetagenerationMatch
_ocIfGenerationNotMatch
_ocIfSourceMetagenerationNotMatch
_ocIfSourceMetagenerationMatch
_ocIfGenerationMatch
_ocUserProject
_ocIfMetagenerationNotMatch
_ocIfSourceGenerationNotMatch
_ocProjection
_ocSourceGeneration
(Just AltJSON)
_ocPayload
storageService
where go
= buildClient (Proxy :: Proxy ObjectsCopyResource)
mempty