{-# 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.Videos.Rate
(
VideosRateResource
, videosRate
, VideosRate
, vrRating
, vrId
) where
import Network.Google.Prelude
import Network.Google.YouTube.Types
type VideosRateResource =
"youtube" :>
"v3" :>
"videos" :>
"rate" :>
QueryParam "id" Text :>
QueryParam "rating" VideosRateRating :>
QueryParam "alt" AltJSON :> Post '[JSON] ()
data VideosRate = VideosRate'
{ _vrRating :: !VideosRateRating
, _vrId :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
videosRate
:: VideosRateRating
-> Text
-> VideosRate
videosRate pVrRating_ pVrId_ =
VideosRate'
{ _vrRating = pVrRating_
, _vrId = pVrId_
}
vrRating :: Lens' VideosRate VideosRateRating
vrRating = lens _vrRating (\ s a -> s{_vrRating = a})
vrId :: Lens' VideosRate Text
vrId = lens _vrId (\ s a -> s{_vrId = a})
instance GoogleRequest VideosRate where
type Rs VideosRate = ()
type Scopes VideosRate =
'["https://www.googleapis.com/auth/youtube",
"https://www.googleapis.com/auth/youtube.force-ssl",
"https://www.googleapis.com/auth/youtubepartner"]
requestClient VideosRate'{..}
= go (Just _vrId) (Just _vrRating) (Just AltJSON)
youTubeService
where go
= buildClient (Proxy :: Proxy VideosRateResource)
mempty