{-# 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.YouTube.Captions.Insert
(
CaptionsInsertResource
, captionsInsert
, CaptionsInsert
, ciOnBehalfOf
, ciPart
, ciPayload
, ciOnBehalfOfContentOwner
, ciSync
) where
import Network.Google.Prelude
import Network.Google.YouTube.Types
type CaptionsInsertResource =
"youtube" :>
"v3" :>
"captions" :>
QueryParam "part" Text :>
QueryParam "onBehalfOf" Text :>
QueryParam "onBehalfOfContentOwner" Text :>
QueryParam "sync" Bool :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Caption :> Post '[JSON] Caption
:<|>
"upload" :>
"youtube" :>
"v3" :>
"captions" :>
QueryParam "part" Text :>
QueryParam "onBehalfOf" Text :>
QueryParam "onBehalfOfContentOwner" Text :>
QueryParam "sync" Bool :>
QueryParam "alt" AltJSON :>
QueryParam "uploadType" Multipart :>
MultipartRelated '[JSON] Caption :>
Post '[JSON] Caption
data CaptionsInsert = CaptionsInsert'
{ _ciOnBehalfOf :: !(Maybe Text)
, _ciPart :: !Text
, _ciPayload :: !Caption
, _ciOnBehalfOfContentOwner :: !(Maybe Text)
, _ciSync :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
captionsInsert
:: Text
-> Caption
-> CaptionsInsert
captionsInsert pCiPart_ pCiPayload_ =
CaptionsInsert'
{ _ciOnBehalfOf = Nothing
, _ciPart = pCiPart_
, _ciPayload = pCiPayload_
, _ciOnBehalfOfContentOwner = Nothing
, _ciSync = Nothing
}
ciOnBehalfOf :: Lens' CaptionsInsert (Maybe Text)
ciOnBehalfOf
= lens _ciOnBehalfOf (\ s a -> s{_ciOnBehalfOf = a})
ciPart :: Lens' CaptionsInsert Text
ciPart = lens _ciPart (\ s a -> s{_ciPart = a})
ciPayload :: Lens' CaptionsInsert Caption
ciPayload
= lens _ciPayload (\ s a -> s{_ciPayload = a})
ciOnBehalfOfContentOwner :: Lens' CaptionsInsert (Maybe Text)
ciOnBehalfOfContentOwner
= lens _ciOnBehalfOfContentOwner
(\ s a -> s{_ciOnBehalfOfContentOwner = a})
ciSync :: Lens' CaptionsInsert (Maybe Bool)
ciSync = lens _ciSync (\ s a -> s{_ciSync = a})
instance GoogleRequest CaptionsInsert where
type Rs CaptionsInsert = Caption
type Scopes CaptionsInsert =
'["https://www.googleapis.com/auth/youtube.force-ssl",
"https://www.googleapis.com/auth/youtubepartner"]
requestClient CaptionsInsert'{..}
= go (Just _ciPart) _ciOnBehalfOf
_ciOnBehalfOfContentOwner
_ciSync
(Just AltJSON)
_ciPayload
youTubeService
where go :<|> _
= buildClient (Proxy :: Proxy CaptionsInsertResource)
mempty
instance GoogleRequest (MediaUpload CaptionsInsert)
where
type Rs (MediaUpload CaptionsInsert) = Caption
type Scopes (MediaUpload CaptionsInsert) =
Scopes CaptionsInsert
requestClient (MediaUpload CaptionsInsert'{..} body)
= go (Just _ciPart) _ciOnBehalfOf
_ciOnBehalfOfContentOwner
_ciSync
(Just AltJSON)
(Just Multipart)
_ciPayload
body
youTubeService
where _ :<|> go
= buildClient (Proxy :: Proxy CaptionsInsertResource)
mempty