{-# 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.Drive.Files.Update
(
FilesUpdateResource
, filesUpdate
, FilesUpdate
, fuPayload
, fuRemoveParents
, fuUseContentAsIndexableText
, fuOCRLanguage
, fuKeepRevisionForever
, fuFileId
, fuAddParents
, fuSupportsTeamDrives
) where
import Network.Google.Drive.Types
import Network.Google.Prelude
type FilesUpdateResource =
"drive" :>
"v3" :>
"files" :>
Capture "fileId" Text :>
QueryParam "removeParents" Text :>
QueryParam "useContentAsIndexableText" Bool :>
QueryParam "ocrLanguage" Text :>
QueryParam "keepRevisionForever" Bool :>
QueryParam "addParents" Text :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] File :> Patch '[JSON] File
:<|>
"upload" :>
"drive" :>
"v3" :>
"files" :>
Capture "fileId" Text :>
QueryParam "removeParents" Text :>
QueryParam "useContentAsIndexableText" Bool :>
QueryParam "ocrLanguage" Text :>
QueryParam "keepRevisionForever" Bool :>
QueryParam "addParents" Text :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltJSON :>
QueryParam "uploadType" Multipart :>
MultipartRelated '[JSON] File :>
Patch '[JSON] File
data FilesUpdate = FilesUpdate'
{ _fuPayload :: !File
, _fuRemoveParents :: !(Maybe Text)
, _fuUseContentAsIndexableText :: !Bool
, _fuOCRLanguage :: !(Maybe Text)
, _fuKeepRevisionForever :: !Bool
, _fuFileId :: !Text
, _fuAddParents :: !(Maybe Text)
, _fuSupportsTeamDrives :: !Bool
} deriving (Eq,Show,Data,Typeable,Generic)
filesUpdate
:: File
-> Text
-> FilesUpdate
filesUpdate pFuPayload_ pFuFileId_ =
FilesUpdate'
{ _fuPayload = pFuPayload_
, _fuRemoveParents = Nothing
, _fuUseContentAsIndexableText = False
, _fuOCRLanguage = Nothing
, _fuKeepRevisionForever = False
, _fuFileId = pFuFileId_
, _fuAddParents = Nothing
, _fuSupportsTeamDrives = False
}
fuPayload :: Lens' FilesUpdate File
fuPayload
= lens _fuPayload (\ s a -> s{_fuPayload = a})
fuRemoveParents :: Lens' FilesUpdate (Maybe Text)
fuRemoveParents
= lens _fuRemoveParents
(\ s a -> s{_fuRemoveParents = a})
fuUseContentAsIndexableText :: Lens' FilesUpdate Bool
fuUseContentAsIndexableText
= lens _fuUseContentAsIndexableText
(\ s a -> s{_fuUseContentAsIndexableText = a})
fuOCRLanguage :: Lens' FilesUpdate (Maybe Text)
fuOCRLanguage
= lens _fuOCRLanguage
(\ s a -> s{_fuOCRLanguage = a})
fuKeepRevisionForever :: Lens' FilesUpdate Bool
fuKeepRevisionForever
= lens _fuKeepRevisionForever
(\ s a -> s{_fuKeepRevisionForever = a})
fuFileId :: Lens' FilesUpdate Text
fuFileId = lens _fuFileId (\ s a -> s{_fuFileId = a})
fuAddParents :: Lens' FilesUpdate (Maybe Text)
fuAddParents
= lens _fuAddParents (\ s a -> s{_fuAddParents = a})
fuSupportsTeamDrives :: Lens' FilesUpdate Bool
fuSupportsTeamDrives
= lens _fuSupportsTeamDrives
(\ s a -> s{_fuSupportsTeamDrives = a})
instance GoogleRequest FilesUpdate where
type Rs FilesUpdate = File
type Scopes FilesUpdate =
'["https://www.googleapis.com/auth/drive",
"https://www.googleapis.com/auth/drive.appdata",
"https://www.googleapis.com/auth/drive.file",
"https://www.googleapis.com/auth/drive.metadata",
"https://www.googleapis.com/auth/drive.scripts"]
requestClient FilesUpdate'{..}
= go _fuFileId _fuRemoveParents
(Just _fuUseContentAsIndexableText)
_fuOCRLanguage
(Just _fuKeepRevisionForever)
_fuAddParents
(Just _fuSupportsTeamDrives)
(Just AltJSON)
_fuPayload
driveService
where go :<|> _
= buildClient (Proxy :: Proxy FilesUpdateResource)
mempty
instance GoogleRequest (MediaUpload FilesUpdate)
where
type Rs (MediaUpload FilesUpdate) = File
type Scopes (MediaUpload FilesUpdate) =
Scopes FilesUpdate
requestClient (MediaUpload FilesUpdate'{..} body)
= go _fuFileId _fuRemoveParents
(Just _fuUseContentAsIndexableText)
_fuOCRLanguage
(Just _fuKeepRevisionForever)
_fuAddParents
(Just _fuSupportsTeamDrives)
(Just AltJSON)
(Just Multipart)
_fuPayload
body
driveService
where _ :<|> go
= buildClient (Proxy :: Proxy FilesUpdateResource)
mempty