{-# 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.Update
    (
    
      ObjectsUpdateResource
    
    , objectsUpdate
    , ObjectsUpdate
    
    , ouIfMetagenerationMatch
    , ouIfGenerationNotMatch
    , ouIfGenerationMatch
    , ouPredefinedACL
    , ouBucket
    , ouPayload
    , ouUserProject
    , ouIfMetagenerationNotMatch
    , ouObject
    , ouProjection
    , ouGeneration
    ) where
import           Network.Google.Prelude
import           Network.Google.Storage.Types
type ObjectsUpdateResource =
     "storage" :>
       "v1" :>
         "b" :>
           Capture "bucket" Text :>
             "o" :>
               Capture "object" Text :>
                 QueryParam "ifMetagenerationMatch" (Textual Int64) :>
                   QueryParam "ifGenerationNotMatch" (Textual Int64) :>
                     QueryParam "ifGenerationMatch" (Textual Int64) :>
                       QueryParam "predefinedAcl" ObjectsUpdatePredefinedACL
                         :>
                         QueryParam "userProject" Text :>
                           QueryParam "ifMetagenerationNotMatch" (Textual Int64)
                             :>
                             QueryParam "projection" ObjectsUpdateProjection :>
                               QueryParam "generation" (Textual Int64) :>
                                 QueryParam "alt" AltJSON :>
                                   ReqBody '[JSON] Object :> Put '[JSON] Object
data ObjectsUpdate = ObjectsUpdate'
    { _ouIfMetagenerationMatch    :: !(Maybe (Textual Int64))
    , _ouIfGenerationNotMatch     :: !(Maybe (Textual Int64))
    , _ouIfGenerationMatch        :: !(Maybe (Textual Int64))
    , _ouPredefinedACL            :: !(Maybe ObjectsUpdatePredefinedACL)
    , _ouBucket                   :: !Text
    , _ouPayload                  :: !Object
    , _ouUserProject              :: !(Maybe Text)
    , _ouIfMetagenerationNotMatch :: !(Maybe (Textual Int64))
    , _ouObject                   :: !Text
    , _ouProjection               :: !(Maybe ObjectsUpdateProjection)
    , _ouGeneration               :: !(Maybe (Textual Int64))
    } deriving (Eq,Show,Data,Typeable,Generic)
objectsUpdate
    :: Text 
    -> Object 
    -> Text 
    -> ObjectsUpdate
objectsUpdate pOuBucket_ pOuPayload_ pOuObject_ =
    ObjectsUpdate'
    { _ouIfMetagenerationMatch = Nothing
    , _ouIfGenerationNotMatch = Nothing
    , _ouIfGenerationMatch = Nothing
    , _ouPredefinedACL = Nothing
    , _ouBucket = pOuBucket_
    , _ouPayload = pOuPayload_
    , _ouUserProject = Nothing
    , _ouIfMetagenerationNotMatch = Nothing
    , _ouObject = pOuObject_
    , _ouProjection = Nothing
    , _ouGeneration = Nothing
    }
ouIfMetagenerationMatch :: Lens' ObjectsUpdate (Maybe Int64)
ouIfMetagenerationMatch
  = lens _ouIfMetagenerationMatch
      (\ s a -> s{_ouIfMetagenerationMatch = a})
      . mapping _Coerce
ouIfGenerationNotMatch :: Lens' ObjectsUpdate (Maybe Int64)
ouIfGenerationNotMatch
  = lens _ouIfGenerationNotMatch
      (\ s a -> s{_ouIfGenerationNotMatch = a})
      . mapping _Coerce
ouIfGenerationMatch :: Lens' ObjectsUpdate (Maybe Int64)
ouIfGenerationMatch
  = lens _ouIfGenerationMatch
      (\ s a -> s{_ouIfGenerationMatch = a})
      . mapping _Coerce
ouPredefinedACL :: Lens' ObjectsUpdate (Maybe ObjectsUpdatePredefinedACL)
ouPredefinedACL
  = lens _ouPredefinedACL
      (\ s a -> s{_ouPredefinedACL = a})
ouBucket :: Lens' ObjectsUpdate Text
ouBucket = lens _ouBucket (\ s a -> s{_ouBucket = a})
ouPayload :: Lens' ObjectsUpdate Object
ouPayload
  = lens _ouPayload (\ s a -> s{_ouPayload = a})
ouUserProject :: Lens' ObjectsUpdate (Maybe Text)
ouUserProject
  = lens _ouUserProject
      (\ s a -> s{_ouUserProject = a})
ouIfMetagenerationNotMatch :: Lens' ObjectsUpdate (Maybe Int64)
ouIfMetagenerationNotMatch
  = lens _ouIfMetagenerationNotMatch
      (\ s a -> s{_ouIfMetagenerationNotMatch = a})
      . mapping _Coerce
ouObject :: Lens' ObjectsUpdate Text
ouObject = lens _ouObject (\ s a -> s{_ouObject = a})
ouProjection :: Lens' ObjectsUpdate (Maybe ObjectsUpdateProjection)
ouProjection
  = lens _ouProjection (\ s a -> s{_ouProjection = a})
ouGeneration :: Lens' ObjectsUpdate (Maybe Int64)
ouGeneration
  = lens _ouGeneration (\ s a -> s{_ouGeneration = a})
      . mapping _Coerce
instance GoogleRequest ObjectsUpdate where
        type Rs ObjectsUpdate = Object
        type Scopes ObjectsUpdate =
             '["https://www.googleapis.com/auth/cloud-platform",
               "https://www.googleapis.com/auth/devstorage.full_control"]
        requestClient ObjectsUpdate'{..}
          = go _ouBucket _ouObject _ouIfMetagenerationMatch
              _ouIfGenerationNotMatch
              _ouIfGenerationMatch
              _ouPredefinedACL
              _ouUserProject
              _ouIfMetagenerationNotMatch
              _ouProjection
              _ouGeneration
              (Just AltJSON)
              _ouPayload
              storageService
          where go
                  = buildClient (Proxy :: Proxy ObjectsUpdateResource)
                      mempty