{-# 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.Insert
(
ObjectsInsertResource
, objectsInsert
, ObjectsInsert
, oiIfMetagenerationMatch
, oiIfGenerationNotMatch
, oiIfGenerationMatch
, oiPredefinedACL
, oiBucket
, oiPayload
, oiUserProject
, oiName
, oiIfMetagenerationNotMatch
, oiContentEncoding
, oiKmsKeyName
, oiProjection
) where
import Network.Google.Prelude
import Network.Google.Storage.Types
type ObjectsInsertResource =
"storage" :>
"v1" :>
"b" :>
Capture "bucket" Text :>
"o" :>
QueryParam "ifMetagenerationMatch" (Textual Int64) :>
QueryParam "ifGenerationNotMatch" (Textual Int64) :>
QueryParam "ifGenerationMatch" (Textual Int64) :>
QueryParam "predefinedAcl" ObjectsInsertPredefinedACL
:>
QueryParam "userProject" Text :>
QueryParam "name" Text :>
QueryParam "ifMetagenerationNotMatch" (Textual Int64)
:>
QueryParam "contentEncoding" Text :>
QueryParam "kmsKeyName" Text :>
QueryParam "projection" ObjectsInsertProjection
:>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Object :>
Post '[JSON] Object
:<|>
"upload" :>
"storage" :>
"v1" :>
"b" :>
Capture "bucket" Text :>
"o" :>
QueryParam "ifMetagenerationMatch" (Textual Int64) :>
QueryParam "ifGenerationNotMatch" (Textual Int64) :>
QueryParam "ifGenerationMatch" (Textual Int64) :>
QueryParam "predefinedAcl" ObjectsInsertPredefinedACL
:>
QueryParam "userProject" Text :>
QueryParam "name" Text :>
QueryParam "ifMetagenerationNotMatch"
(Textual Int64)
:>
QueryParam "contentEncoding" Text :>
QueryParam "kmsKeyName" Text :>
QueryParam "projection"
ObjectsInsertProjection
:>
QueryParam "alt" AltJSON :>
QueryParam "uploadType" Multipart :>
MultipartRelated '[JSON] Object :>
Post '[JSON] Object
data ObjectsInsert = ObjectsInsert'
{ _oiIfMetagenerationMatch :: !(Maybe (Textual Int64))
, _oiIfGenerationNotMatch :: !(Maybe (Textual Int64))
, _oiIfGenerationMatch :: !(Maybe (Textual Int64))
, _oiPredefinedACL :: !(Maybe ObjectsInsertPredefinedACL)
, _oiBucket :: !Text
, _oiPayload :: !Object
, _oiUserProject :: !(Maybe Text)
, _oiName :: !(Maybe Text)
, _oiIfMetagenerationNotMatch :: !(Maybe (Textual Int64))
, _oiContentEncoding :: !(Maybe Text)
, _oiKmsKeyName :: !(Maybe Text)
, _oiProjection :: !(Maybe ObjectsInsertProjection)
} deriving (Eq,Show,Data,Typeable,Generic)
objectsInsert
:: Text
-> Object
-> ObjectsInsert
objectsInsert pOiBucket_ pOiPayload_ =
ObjectsInsert'
{ _oiIfMetagenerationMatch = Nothing
, _oiIfGenerationNotMatch = Nothing
, _oiIfGenerationMatch = Nothing
, _oiPredefinedACL = Nothing
, _oiBucket = pOiBucket_
, _oiPayload = pOiPayload_
, _oiUserProject = Nothing
, _oiName = Nothing
, _oiIfMetagenerationNotMatch = Nothing
, _oiContentEncoding = Nothing
, _oiKmsKeyName = Nothing
, _oiProjection = Nothing
}
oiIfMetagenerationMatch :: Lens' ObjectsInsert (Maybe Int64)
oiIfMetagenerationMatch
= lens _oiIfMetagenerationMatch
(\ s a -> s{_oiIfMetagenerationMatch = a})
. mapping _Coerce
oiIfGenerationNotMatch :: Lens' ObjectsInsert (Maybe Int64)
oiIfGenerationNotMatch
= lens _oiIfGenerationNotMatch
(\ s a -> s{_oiIfGenerationNotMatch = a})
. mapping _Coerce
oiIfGenerationMatch :: Lens' ObjectsInsert (Maybe Int64)
oiIfGenerationMatch
= lens _oiIfGenerationMatch
(\ s a -> s{_oiIfGenerationMatch = a})
. mapping _Coerce
oiPredefinedACL :: Lens' ObjectsInsert (Maybe ObjectsInsertPredefinedACL)
oiPredefinedACL
= lens _oiPredefinedACL
(\ s a -> s{_oiPredefinedACL = a})
oiBucket :: Lens' ObjectsInsert Text
oiBucket = lens _oiBucket (\ s a -> s{_oiBucket = a})
oiPayload :: Lens' ObjectsInsert Object
oiPayload
= lens _oiPayload (\ s a -> s{_oiPayload = a})
oiUserProject :: Lens' ObjectsInsert (Maybe Text)
oiUserProject
= lens _oiUserProject
(\ s a -> s{_oiUserProject = a})
oiName :: Lens' ObjectsInsert (Maybe Text)
oiName = lens _oiName (\ s a -> s{_oiName = a})
oiIfMetagenerationNotMatch :: Lens' ObjectsInsert (Maybe Int64)
oiIfMetagenerationNotMatch
= lens _oiIfMetagenerationNotMatch
(\ s a -> s{_oiIfMetagenerationNotMatch = a})
. mapping _Coerce
oiContentEncoding :: Lens' ObjectsInsert (Maybe Text)
oiContentEncoding
= lens _oiContentEncoding
(\ s a -> s{_oiContentEncoding = a})
oiKmsKeyName :: Lens' ObjectsInsert (Maybe Text)
oiKmsKeyName
= lens _oiKmsKeyName (\ s a -> s{_oiKmsKeyName = a})
oiProjection :: Lens' ObjectsInsert (Maybe ObjectsInsertProjection)
oiProjection
= lens _oiProjection (\ s a -> s{_oiProjection = a})
instance GoogleRequest ObjectsInsert where
type Rs ObjectsInsert = Object
type Scopes ObjectsInsert =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/devstorage.full_control",
"https://www.googleapis.com/auth/devstorage.read_write"]
requestClient ObjectsInsert'{..}
= go _oiBucket _oiIfMetagenerationMatch
_oiIfGenerationNotMatch
_oiIfGenerationMatch
_oiPredefinedACL
_oiUserProject
_oiName
_oiIfMetagenerationNotMatch
_oiContentEncoding
_oiKmsKeyName
_oiProjection
(Just AltJSON)
_oiPayload
storageService
where go :<|> _
= buildClient (Proxy :: Proxy ObjectsInsertResource)
mempty
instance GoogleRequest (MediaUpload ObjectsInsert)
where
type Rs (MediaUpload ObjectsInsert) = Object
type Scopes (MediaUpload ObjectsInsert) =
Scopes ObjectsInsert
requestClient (MediaUpload ObjectsInsert'{..} body)
= go _oiBucket _oiIfMetagenerationMatch
_oiIfGenerationNotMatch
_oiIfGenerationMatch
_oiPredefinedACL
_oiUserProject
_oiName
_oiIfMetagenerationNotMatch
_oiContentEncoding
_oiKmsKeyName
_oiProjection
(Just AltJSON)
(Just Multipart)
_oiPayload
body
storageService
where _ :<|> go
= buildClient (Proxy :: Proxy ObjectsInsertResource)
mempty