{-# 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.Create
(
FilesCreateResource
, filesCreate
, FilesCreate
, fcPayload
, fcUseContentAsIndexableText
, fcOCRLanguage
, fcKeepRevisionForever
, fcIgnoreDefaultVisibility
, fcSupportsTeamDrives
) where
import Network.Google.Drive.Types
import Network.Google.Prelude
type FilesCreateResource =
"drive" :>
"v3" :>
"files" :>
QueryParam "useContentAsIndexableText" Bool :>
QueryParam "ocrLanguage" Text :>
QueryParam "keepRevisionForever" Bool :>
QueryParam "ignoreDefaultVisibility" Bool :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] File :> Post '[JSON] File
:<|>
"upload" :>
"drive" :>
"v3" :>
"files" :>
QueryParam "useContentAsIndexableText" Bool :>
QueryParam "ocrLanguage" Text :>
QueryParam "keepRevisionForever" Bool :>
QueryParam "ignoreDefaultVisibility" Bool :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltJSON :>
QueryParam "uploadType" Multipart :>
MultipartRelated '[JSON] File :> Post '[JSON] File
data FilesCreate = FilesCreate'
{ _fcPayload :: !File
, _fcUseContentAsIndexableText :: !Bool
, _fcOCRLanguage :: !(Maybe Text)
, _fcKeepRevisionForever :: !Bool
, _fcIgnoreDefaultVisibility :: !Bool
, _fcSupportsTeamDrives :: !Bool
} deriving (Eq,Show,Data,Typeable,Generic)
filesCreate
:: File
-> FilesCreate
filesCreate pFcPayload_ =
FilesCreate'
{ _fcPayload = pFcPayload_
, _fcUseContentAsIndexableText = False
, _fcOCRLanguage = Nothing
, _fcKeepRevisionForever = False
, _fcIgnoreDefaultVisibility = False
, _fcSupportsTeamDrives = False
}
fcPayload :: Lens' FilesCreate File
fcPayload
= lens _fcPayload (\ s a -> s{_fcPayload = a})
fcUseContentAsIndexableText :: Lens' FilesCreate Bool
fcUseContentAsIndexableText
= lens _fcUseContentAsIndexableText
(\ s a -> s{_fcUseContentAsIndexableText = a})
fcOCRLanguage :: Lens' FilesCreate (Maybe Text)
fcOCRLanguage
= lens _fcOCRLanguage
(\ s a -> s{_fcOCRLanguage = a})
fcKeepRevisionForever :: Lens' FilesCreate Bool
fcKeepRevisionForever
= lens _fcKeepRevisionForever
(\ s a -> s{_fcKeepRevisionForever = a})
fcIgnoreDefaultVisibility :: Lens' FilesCreate Bool
fcIgnoreDefaultVisibility
= lens _fcIgnoreDefaultVisibility
(\ s a -> s{_fcIgnoreDefaultVisibility = a})
fcSupportsTeamDrives :: Lens' FilesCreate Bool
fcSupportsTeamDrives
= lens _fcSupportsTeamDrives
(\ s a -> s{_fcSupportsTeamDrives = a})
instance GoogleRequest FilesCreate where
type Rs FilesCreate = File
type Scopes FilesCreate =
'["https://www.googleapis.com/auth/drive",
"https://www.googleapis.com/auth/drive.appdata",
"https://www.googleapis.com/auth/drive.file"]
requestClient FilesCreate'{..}
= go (Just _fcUseContentAsIndexableText)
_fcOCRLanguage
(Just _fcKeepRevisionForever)
(Just _fcIgnoreDefaultVisibility)
(Just _fcSupportsTeamDrives)
(Just AltJSON)
_fcPayload
driveService
where go :<|> _
= buildClient (Proxy :: Proxy FilesCreateResource)
mempty
instance GoogleRequest (MediaUpload FilesCreate)
where
type Rs (MediaUpload FilesCreate) = File
type Scopes (MediaUpload FilesCreate) =
Scopes FilesCreate
requestClient (MediaUpload FilesCreate'{..} body)
= go (Just _fcUseContentAsIndexableText)
_fcOCRLanguage
(Just _fcKeepRevisionForever)
(Just _fcIgnoreDefaultVisibility)
(Just _fcSupportsTeamDrives)
(Just AltJSON)
(Just Multipart)
_fcPayload
body
driveService
where _ :<|> go
= buildClient (Proxy :: Proxy FilesCreateResource)
mempty