{-# 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.List
(
TasksListResource
, tasksList
, TasksList
, tlDueMax
, tlShowDeleted
, tlShowCompleted
, tlDueMin
, tlShowHidden
, tlCompletedMax
, tlUpdatedMin
, tlTaskList
, tlCompletedMin
, tlPageToken
, tlMaxResults
) where
import Network.Google.AppsTasks.Types
import Network.Google.Prelude
type TasksListResource =
"tasks" :>
"v1" :>
"lists" :>
Capture "tasklist" Text :>
"tasks" :>
QueryParam "dueMax" Text :>
QueryParam "showDeleted" Bool :>
QueryParam "showCompleted" Bool :>
QueryParam "dueMin" Text :>
QueryParam "showHidden" Bool :>
QueryParam "completedMax" Text :>
QueryParam "updatedMin" Text :>
QueryParam "completedMin" Text :>
QueryParam "pageToken" Text :>
QueryParam "maxResults" (Textual Int64) :>
QueryParam "alt" AltJSON :> Get '[JSON] Tasks
data TasksList = TasksList'
{ _tlDueMax :: !(Maybe Text)
, _tlShowDeleted :: !(Maybe Bool)
, _tlShowCompleted :: !(Maybe Bool)
, _tlDueMin :: !(Maybe Text)
, _tlShowHidden :: !(Maybe Bool)
, _tlCompletedMax :: !(Maybe Text)
, _tlUpdatedMin :: !(Maybe Text)
, _tlTaskList :: !Text
, _tlCompletedMin :: !(Maybe Text)
, _tlPageToken :: !(Maybe Text)
, _tlMaxResults :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
tasksList
:: Text
-> TasksList
tasksList pTlTaskList_ =
TasksList'
{ _tlDueMax = Nothing
, _tlShowDeleted = Nothing
, _tlShowCompleted = Nothing
, _tlDueMin = Nothing
, _tlShowHidden = Nothing
, _tlCompletedMax = Nothing
, _tlUpdatedMin = Nothing
, _tlTaskList = pTlTaskList_
, _tlCompletedMin = Nothing
, _tlPageToken = Nothing
, _tlMaxResults = Nothing
}
tlDueMax :: Lens' TasksList (Maybe Text)
tlDueMax = lens _tlDueMax (\ s a -> s{_tlDueMax = a})
tlShowDeleted :: Lens' TasksList (Maybe Bool)
tlShowDeleted
= lens _tlShowDeleted
(\ s a -> s{_tlShowDeleted = a})
tlShowCompleted :: Lens' TasksList (Maybe Bool)
tlShowCompleted
= lens _tlShowCompleted
(\ s a -> s{_tlShowCompleted = a})
tlDueMin :: Lens' TasksList (Maybe Text)
tlDueMin = lens _tlDueMin (\ s a -> s{_tlDueMin = a})
tlShowHidden :: Lens' TasksList (Maybe Bool)
tlShowHidden
= lens _tlShowHidden (\ s a -> s{_tlShowHidden = a})
tlCompletedMax :: Lens' TasksList (Maybe Text)
tlCompletedMax
= lens _tlCompletedMax
(\ s a -> s{_tlCompletedMax = a})
tlUpdatedMin :: Lens' TasksList (Maybe Text)
tlUpdatedMin
= lens _tlUpdatedMin (\ s a -> s{_tlUpdatedMin = a})
tlTaskList :: Lens' TasksList Text
tlTaskList
= lens _tlTaskList (\ s a -> s{_tlTaskList = a})
tlCompletedMin :: Lens' TasksList (Maybe Text)
tlCompletedMin
= lens _tlCompletedMin
(\ s a -> s{_tlCompletedMin = a})
tlPageToken :: Lens' TasksList (Maybe Text)
tlPageToken
= lens _tlPageToken (\ s a -> s{_tlPageToken = a})
tlMaxResults :: Lens' TasksList (Maybe Int64)
tlMaxResults
= lens _tlMaxResults (\ s a -> s{_tlMaxResults = a})
. mapping _Coerce
instance GoogleRequest TasksList where
type Rs TasksList = Tasks
type Scopes TasksList =
'["https://www.googleapis.com/auth/tasks",
"https://www.googleapis.com/auth/tasks.readonly"]
requestClient TasksList'{..}
= go _tlTaskList _tlDueMax _tlShowDeleted
_tlShowCompleted
_tlDueMin
_tlShowHidden
_tlCompletedMax
_tlUpdatedMin
_tlCompletedMin
_tlPageToken
_tlMaxResults
(Just AltJSON)
appsTasksService
where go
= buildClient (Proxy :: Proxy TasksListResource)
mempty