{-# 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.Get
(
FilesGetResource
, filesGet
, FilesGet
, fgAcknowledgeAbuse
, fgFileId
, fgSupportsTeamDrives
) where
import Network.Google.Drive.Types
import Network.Google.Prelude
type FilesGetResource =
"drive" :>
"v3" :>
"files" :>
Capture "fileId" Text :>
QueryParam "acknowledgeAbuse" Bool :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltJSON :> Get '[JSON] File
:<|>
"drive" :>
"v3" :>
"files" :>
Capture "fileId" Text :>
QueryParam "acknowledgeAbuse" Bool :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltMedia :>
Get '[OctetStream] Stream
data FilesGet = FilesGet'
{ _fgAcknowledgeAbuse :: !Bool
, _fgFileId :: !Text
, _fgSupportsTeamDrives :: !Bool
} deriving (Eq,Show,Data,Typeable,Generic)
filesGet
:: Text
-> FilesGet
filesGet pFgFileId_ =
FilesGet'
{ _fgAcknowledgeAbuse = False
, _fgFileId = pFgFileId_
, _fgSupportsTeamDrives = False
}
fgAcknowledgeAbuse :: Lens' FilesGet Bool
fgAcknowledgeAbuse
= lens _fgAcknowledgeAbuse
(\ s a -> s{_fgAcknowledgeAbuse = a})
fgFileId :: Lens' FilesGet Text
fgFileId = lens _fgFileId (\ s a -> s{_fgFileId = a})
fgSupportsTeamDrives :: Lens' FilesGet Bool
fgSupportsTeamDrives
= lens _fgSupportsTeamDrives
(\ s a -> s{_fgSupportsTeamDrives = a})
instance GoogleRequest FilesGet where
type Rs FilesGet = File
type Scopes FilesGet =
'["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.metadata.readonly",
"https://www.googleapis.com/auth/drive.photos.readonly",
"https://www.googleapis.com/auth/drive.readonly"]
requestClient FilesGet'{..}
= go _fgFileId (Just _fgAcknowledgeAbuse)
(Just _fgSupportsTeamDrives)
(Just AltJSON)
driveService
where go :<|> _
= buildClient (Proxy :: Proxy FilesGetResource)
mempty
instance GoogleRequest (MediaDownload FilesGet) where
type Rs (MediaDownload FilesGet) = Stream
type Scopes (MediaDownload FilesGet) =
Scopes FilesGet
requestClient (MediaDownload FilesGet'{..})
= go _fgFileId (Just _fgAcknowledgeAbuse)
(Just _fgSupportsTeamDrives)
(Just AltMedia)
driveService
where _ :<|> go
= buildClient (Proxy :: Proxy FilesGetResource)
mempty