{-# 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.Gmail.Users.Drafts.Create
(
UsersDraftsCreateResource
, usersDraftsCreate
, UsersDraftsCreate
, udcPayload
, udcUserId
) where
import Network.Google.Gmail.Types
import Network.Google.Prelude
type UsersDraftsCreateResource =
"gmail" :>
"v1" :>
"users" :>
Capture "userId" Text :>
"drafts" :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Draft :> Post '[JSON] Draft
:<|>
"upload" :>
"gmail" :>
"v1" :>
"users" :>
Capture "userId" Text :>
"drafts" :>
QueryParam "alt" AltJSON :>
QueryParam "uploadType" Multipart :>
MultipartRelated '[JSON] Draft :> Post '[JSON] Draft
data UsersDraftsCreate = UsersDraftsCreate'
{ _udcPayload :: !Draft
, _udcUserId :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
usersDraftsCreate
:: Draft
-> UsersDraftsCreate
usersDraftsCreate pUdcPayload_ =
UsersDraftsCreate'
{ _udcPayload = pUdcPayload_
, _udcUserId = "me"
}
udcPayload :: Lens' UsersDraftsCreate Draft
udcPayload
= lens _udcPayload (\ s a -> s{_udcPayload = a})
udcUserId :: Lens' UsersDraftsCreate Text
udcUserId
= lens _udcUserId (\ s a -> s{_udcUserId = a})
instance GoogleRequest UsersDraftsCreate where
type Rs UsersDraftsCreate = Draft
type Scopes UsersDraftsCreate =
'["https://mail.google.com/",
"https://www.googleapis.com/auth/gmail.compose",
"https://www.googleapis.com/auth/gmail.modify"]
requestClient UsersDraftsCreate'{..}
= go _udcUserId (Just AltJSON) _udcPayload
gmailService
where go :<|> _
= buildClient
(Proxy :: Proxy UsersDraftsCreateResource)
mempty
instance GoogleRequest
(MediaUpload UsersDraftsCreate) where
type Rs (MediaUpload UsersDraftsCreate) = Draft
type Scopes (MediaUpload UsersDraftsCreate) =
Scopes UsersDraftsCreate
requestClient
(MediaUpload UsersDraftsCreate'{..} body)
= go _udcUserId (Just AltJSON) (Just Multipart)
_udcPayload
body
gmailService
where _ :<|> go
= buildClient
(Proxy :: Proxy UsersDraftsCreateResource)
mempty