{-# 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.Tasks.Tasks.Insert
(
TasksInsertResource
, tasksInsert
, TasksInsert
, tiParent
, tiPayload
, tiTaskList
, tiPrevious
) where
import Network.Google.AppsTasks.Types
import Network.Google.Prelude
type TasksInsertResource =
"tasks" :>
"v1" :>
"lists" :>
Capture "tasklist" Text :>
"tasks" :>
QueryParam "parent" Text :>
QueryParam "previous" Text :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Task :> Post '[JSON] Task
data TasksInsert = TasksInsert'
{ _tiParent :: !(Maybe Text)
, _tiPayload :: !Task
, _tiTaskList :: !Text
, _tiPrevious :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
tasksInsert
:: Task
-> Text
-> TasksInsert
tasksInsert pTiPayload_ pTiTaskList_ =
TasksInsert'
{ _tiParent = Nothing
, _tiPayload = pTiPayload_
, _tiTaskList = pTiTaskList_
, _tiPrevious = Nothing
}
tiParent :: Lens' TasksInsert (Maybe Text)
tiParent = lens _tiParent (\ s a -> s{_tiParent = a})
tiPayload :: Lens' TasksInsert Task
tiPayload
= lens _tiPayload (\ s a -> s{_tiPayload = a})
tiTaskList :: Lens' TasksInsert Text
tiTaskList
= lens _tiTaskList (\ s a -> s{_tiTaskList = a})
tiPrevious :: Lens' TasksInsert (Maybe Text)
tiPrevious
= lens _tiPrevious (\ s a -> s{_tiPrevious = a})
instance GoogleRequest TasksInsert where
type Rs TasksInsert = Task
type Scopes TasksInsert =
'["https://www.googleapis.com/auth/tasks"]
requestClient TasksInsert'{..}
= go _tiTaskList _tiParent _tiPrevious (Just AltJSON)
_tiPayload
appsTasksService
where go
= buildClient (Proxy :: Proxy TasksInsertResource)
mempty