{-# 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.Watch
(
FilesWatchResource
, filesWatch
, FilesWatch
, fwPayload
, fwAcknowledgeAbuse
, fwFileId
, fwSupportsTeamDrives
) where
import Network.Google.Drive.Types
import Network.Google.Prelude
type FilesWatchResource =
"drive" :>
"v3" :>
"files" :>
Capture "fileId" Text :>
"watch" :>
QueryParam "acknowledgeAbuse" Bool :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Channel :> Post '[JSON] Channel
:<|>
"drive" :>
"v3" :>
"files" :>
Capture "fileId" Text :>
"watch" :>
QueryParam "acknowledgeAbuse" Bool :>
QueryParam "supportsTeamDrives" Bool :>
QueryParam "alt" AltMedia :>
Post '[OctetStream] Stream
data FilesWatch = FilesWatch'
{ _fwPayload :: !Channel
, _fwAcknowledgeAbuse :: !Bool
, _fwFileId :: !Text
, _fwSupportsTeamDrives :: !Bool
} deriving (Eq,Show,Data,Typeable,Generic)
filesWatch
:: Channel
-> Text
-> FilesWatch
filesWatch pFwPayload_ pFwFileId_ =
FilesWatch'
{ _fwPayload = pFwPayload_
, _fwAcknowledgeAbuse = False
, _fwFileId = pFwFileId_
, _fwSupportsTeamDrives = False
}
fwPayload :: Lens' FilesWatch Channel
fwPayload
= lens _fwPayload (\ s a -> s{_fwPayload = a})
fwAcknowledgeAbuse :: Lens' FilesWatch Bool
fwAcknowledgeAbuse
= lens _fwAcknowledgeAbuse
(\ s a -> s{_fwAcknowledgeAbuse = a})
fwFileId :: Lens' FilesWatch Text
fwFileId = lens _fwFileId (\ s a -> s{_fwFileId = a})
fwSupportsTeamDrives :: Lens' FilesWatch Bool
fwSupportsTeamDrives
= lens _fwSupportsTeamDrives
(\ s a -> s{_fwSupportsTeamDrives = a})
instance GoogleRequest FilesWatch where
type Rs FilesWatch = Channel
type Scopes FilesWatch =
'["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 FilesWatch'{..}
= go _fwFileId (Just _fwAcknowledgeAbuse)
(Just _fwSupportsTeamDrives)
(Just AltJSON)
_fwPayload
driveService
where go :<|> _
= buildClient (Proxy :: Proxy FilesWatchResource)
mempty
instance GoogleRequest (MediaDownload FilesWatch)
where
type Rs (MediaDownload FilesWatch) = Stream
type Scopes (MediaDownload FilesWatch) =
Scopes FilesWatch
requestClient (MediaDownload FilesWatch'{..})
= go _fwFileId (Just _fwAcknowledgeAbuse)
(Just _fwSupportsTeamDrives)
(Just AltMedia)
driveService
where _ :<|> go
= buildClient (Proxy :: Proxy FilesWatchResource)
mempty