{-# 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.CommentThreads.Insert
(
CommentThreadsInsertResource
, commentThreadsInsert
, CommentThreadsInsert
, ctiPart
, ctiPayload
) where
import Network.Google.Prelude
import Network.Google.YouTube.Types
type CommentThreadsInsertResource =
"youtube" :>
"v3" :>
"commentThreads" :>
QueryParam "part" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] CommentThread :>
Post '[JSON] CommentThread
data CommentThreadsInsert = CommentThreadsInsert'
{ _ctiPart :: !Text
, _ctiPayload :: !CommentThread
} deriving (Eq,Show,Data,Typeable,Generic)
commentThreadsInsert
:: Text
-> CommentThread
-> CommentThreadsInsert
commentThreadsInsert pCtiPart_ pCtiPayload_ =
CommentThreadsInsert'
{ _ctiPart = pCtiPart_
, _ctiPayload = pCtiPayload_
}
ctiPart :: Lens' CommentThreadsInsert Text
ctiPart = lens _ctiPart (\ s a -> s{_ctiPart = a})
ctiPayload :: Lens' CommentThreadsInsert CommentThread
ctiPayload
= lens _ctiPayload (\ s a -> s{_ctiPayload = a})
instance GoogleRequest CommentThreadsInsert where
type Rs CommentThreadsInsert = CommentThread
type Scopes CommentThreadsInsert =
'["https://www.googleapis.com/auth/youtube.force-ssl"]
requestClient CommentThreadsInsert'{..}
= go (Just _ctiPart) (Just AltJSON) _ctiPayload
youTubeService
where go
= buildClient
(Proxy :: Proxy CommentThreadsInsertResource)
mempty