{-# 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.Blogger.Posts.Patch
(
PostsPatchResource
, postsPatch
, PostsPatch
, posoFetchBody
, posoFetchImages
, posoBlogId
, posoPayload
, posoMaxComments
, posoRevert
, posoPostId
, posoPublish
) where
import Network.Google.Blogger.Types
import Network.Google.Prelude
type PostsPatchResource =
"blogger" :>
"v3" :>
"blogs" :>
Capture "blogId" Text :>
"posts" :>
Capture "postId" Text :>
QueryParam "fetchBody" Bool :>
QueryParam "fetchImages" Bool :>
QueryParam "maxComments" (Textual Word32) :>
QueryParam "revert" Bool :>
QueryParam "publish" Bool :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Post' :> Patch '[JSON] Post'
data PostsPatch = PostsPatch'
{ _posoFetchBody :: !Bool
, _posoFetchImages :: !(Maybe Bool)
, _posoBlogId :: !Text
, _posoPayload :: !Post'
, _posoMaxComments :: !(Maybe (Textual Word32))
, _posoRevert :: !(Maybe Bool)
, _posoPostId :: !Text
, _posoPublish :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
postsPatch
:: Text
-> Post'
-> Text
-> PostsPatch
postsPatch pPosoBlogId_ pPosoPayload_ pPosoPostId_ =
PostsPatch'
{ _posoFetchBody = True
, _posoFetchImages = Nothing
, _posoBlogId = pPosoBlogId_
, _posoPayload = pPosoPayload_
, _posoMaxComments = Nothing
, _posoRevert = Nothing
, _posoPostId = pPosoPostId_
, _posoPublish = Nothing
}
posoFetchBody :: Lens' PostsPatch Bool
posoFetchBody
= lens _posoFetchBody
(\ s a -> s{_posoFetchBody = a})
posoFetchImages :: Lens' PostsPatch (Maybe Bool)
posoFetchImages
= lens _posoFetchImages
(\ s a -> s{_posoFetchImages = a})
posoBlogId :: Lens' PostsPatch Text
posoBlogId
= lens _posoBlogId (\ s a -> s{_posoBlogId = a})
posoPayload :: Lens' PostsPatch Post'
posoPayload
= lens _posoPayload (\ s a -> s{_posoPayload = a})
posoMaxComments :: Lens' PostsPatch (Maybe Word32)
posoMaxComments
= lens _posoMaxComments
(\ s a -> s{_posoMaxComments = a})
. mapping _Coerce
posoRevert :: Lens' PostsPatch (Maybe Bool)
posoRevert
= lens _posoRevert (\ s a -> s{_posoRevert = a})
posoPostId :: Lens' PostsPatch Text
posoPostId
= lens _posoPostId (\ s a -> s{_posoPostId = a})
posoPublish :: Lens' PostsPatch (Maybe Bool)
posoPublish
= lens _posoPublish (\ s a -> s{_posoPublish = a})
instance GoogleRequest PostsPatch where
type Rs PostsPatch = Post'
type Scopes PostsPatch =
'["https://www.googleapis.com/auth/blogger"]
requestClient PostsPatch'{..}
= go _posoBlogId _posoPostId (Just _posoFetchBody)
_posoFetchImages
_posoMaxComments
_posoRevert
_posoPublish
(Just AltJSON)
_posoPayload
bloggerService
where go
= buildClient (Proxy :: Proxy PostsPatchResource)
mempty