gogol-taskqueue-0.3.0: Google TaskQueue SDK.

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Google.TaskQueue.Types

Contents

Description

 

Synopsis

Service Configuration

taskQueueService :: ServiceConfig Source #

Default request referring to version v1beta2 of the TaskQueue API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

taskQueueConsumerScope :: Proxy '["https://www.googleapis.com/auth/taskqueue.consumer"] Source #

Consume Tasks from your Taskqueues

taskQueueScope :: Proxy '["https://www.googleapis.com/auth/taskqueue"] Source #

Manage your Tasks and Taskqueues

Tasks2

data Tasks2 Source #

Instances

Eq Tasks2 Source # 

Methods

(==) :: Tasks2 -> Tasks2 -> Bool #

(/=) :: Tasks2 -> Tasks2 -> Bool #

Data Tasks2 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tasks2 -> c Tasks2 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tasks2 #

toConstr :: Tasks2 -> Constr #

dataTypeOf :: Tasks2 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tasks2) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tasks2) #

gmapT :: (forall b. Data b => b -> b) -> Tasks2 -> Tasks2 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tasks2 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tasks2 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tasks2 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tasks2 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tasks2 -> m Tasks2 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tasks2 -> m Tasks2 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tasks2 -> m Tasks2 #

Show Tasks2 Source # 
Generic Tasks2 Source # 

Associated Types

type Rep Tasks2 :: * -> * #

Methods

from :: Tasks2 -> Rep Tasks2 x #

to :: Rep Tasks2 x -> Tasks2 #

ToJSON Tasks2 Source # 
FromJSON Tasks2 Source # 
type Rep Tasks2 Source # 
type Rep Tasks2 = D1 (MetaData "Tasks2" "Network.Google.TaskQueue.Types.Product" "gogol-taskqueue-0.3.0-De6GncU4nRo3TG29sWTEtK" False) (C1 (MetaCons "Tasks2'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_tItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Task])))))

tasks2 :: Tasks2 Source #

Creates a value of Tasks2 with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tKind :: Lens' Tasks2 Text Source #

The kind of object returned, a list of tasks.

tItems :: Lens' Tasks2 [Task] Source #

The actual list of tasks currently active in the TaskQueue.

TaskQueue

data TaskQueue Source #

Instances

Eq TaskQueue Source # 
Data TaskQueue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TaskQueue -> c TaskQueue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TaskQueue #

toConstr :: TaskQueue -> Constr #

dataTypeOf :: TaskQueue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TaskQueue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaskQueue) #

gmapT :: (forall b. Data b => b -> b) -> TaskQueue -> TaskQueue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TaskQueue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TaskQueue -> r #

gmapQ :: (forall d. Data d => d -> u) -> TaskQueue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TaskQueue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TaskQueue -> m TaskQueue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TaskQueue -> m TaskQueue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TaskQueue -> m TaskQueue #

Show TaskQueue Source # 
Generic TaskQueue Source # 

Associated Types

type Rep TaskQueue :: * -> * #

ToJSON TaskQueue Source # 
FromJSON TaskQueue Source # 
type Rep TaskQueue Source # 

taskQueue :: TaskQueue Source #

Creates a value of TaskQueue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tqKind :: Lens' TaskQueue Text Source #

The kind of REST object returned, in this case taskqueue.

tqStats :: Lens' TaskQueue (Maybe TaskQueueStats) Source #

Statistics for the TaskQueue object in question.

tqMaxLeases :: Lens' TaskQueue (Maybe Int32) Source #

The number of times we should lease out tasks before giving up on them. If unset we lease them out forever until a worker deletes the task.

tqId :: Lens' TaskQueue (Maybe Text) Source #

Name of the taskqueue.

tqACL :: Lens' TaskQueue (Maybe TaskQueueACL) Source #

ACLs that are applicable to this TaskQueue object.

TaskQueueACL

data TaskQueueACL Source #

ACLs that are applicable to this TaskQueue object.

See: taskQueueACL smart constructor.

Instances

Eq TaskQueueACL Source # 
Data TaskQueueACL Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TaskQueueACL -> c TaskQueueACL #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TaskQueueACL #

toConstr :: TaskQueueACL -> Constr #

dataTypeOf :: TaskQueueACL -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TaskQueueACL) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaskQueueACL) #

gmapT :: (forall b. Data b => b -> b) -> TaskQueueACL -> TaskQueueACL #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TaskQueueACL -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TaskQueueACL -> r #

gmapQ :: (forall d. Data d => d -> u) -> TaskQueueACL -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TaskQueueACL -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TaskQueueACL -> m TaskQueueACL #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TaskQueueACL -> m TaskQueueACL #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TaskQueueACL -> m TaskQueueACL #

Show TaskQueueACL Source # 
Generic TaskQueueACL Source # 

Associated Types

type Rep TaskQueueACL :: * -> * #

ToJSON TaskQueueACL Source # 
FromJSON TaskQueueACL Source # 
type Rep TaskQueueACL Source # 
type Rep TaskQueueACL = D1 (MetaData "TaskQueueACL" "Network.Google.TaskQueue.Types.Product" "gogol-taskqueue-0.3.0-De6GncU4nRo3TG29sWTEtK" False) (C1 (MetaCons "TaskQueueACL'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tqaProducerEmails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_tqaAdminEmails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_tqaConsumerEmails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))

taskQueueACL :: TaskQueueACL Source #

Creates a value of TaskQueueACL with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tqaProducerEmails :: Lens' TaskQueueACL [Text] Source #

Email addresses of users who can "produce" tasks into the TaskQueue. This means they can Insert tasks into the queue.

tqaAdminEmails :: Lens' TaskQueueACL [Text] Source #

Email addresses of users who are "admins" of the TaskQueue. This means they can control the queue, eg set ACLs for the queue.

tqaConsumerEmails :: Lens' TaskQueueACL [Text] Source #

Email addresses of users who can "consume" tasks from the TaskQueue. This means they can Dequeue and Delete tasks from the queue.

TaskQueueStats

data TaskQueueStats Source #

Statistics for the TaskQueue object in question.

See: taskQueueStats smart constructor.

Instances

Eq TaskQueueStats Source # 
Data TaskQueueStats Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TaskQueueStats -> c TaskQueueStats #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TaskQueueStats #

toConstr :: TaskQueueStats -> Constr #

dataTypeOf :: TaskQueueStats -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TaskQueueStats) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaskQueueStats) #

gmapT :: (forall b. Data b => b -> b) -> TaskQueueStats -> TaskQueueStats #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TaskQueueStats -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TaskQueueStats -> r #

gmapQ :: (forall d. Data d => d -> u) -> TaskQueueStats -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TaskQueueStats -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TaskQueueStats -> m TaskQueueStats #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TaskQueueStats -> m TaskQueueStats #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TaskQueueStats -> m TaskQueueStats #

Show TaskQueueStats Source # 
Generic TaskQueueStats Source # 

Associated Types

type Rep TaskQueueStats :: * -> * #

ToJSON TaskQueueStats Source # 
FromJSON TaskQueueStats Source # 
type Rep TaskQueueStats Source # 
type Rep TaskQueueStats = D1 (MetaData "TaskQueueStats" "Network.Google.TaskQueue.Types.Product" "gogol-taskqueue-0.3.0-De6GncU4nRo3TG29sWTEtK" False) (C1 (MetaCons "TaskQueueStats'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tqsTotalTasks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_tqsOldestTask") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_tqsLeasedLastHour") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_tqsLeasedLastMinute") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

taskQueueStats :: TaskQueueStats Source #

Creates a value of TaskQueueStats with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tqsTotalTasks :: Lens' TaskQueueStats (Maybe Int32) Source #

Number of tasks in the queue.

tqsOldestTask :: Lens' TaskQueueStats (Maybe Int64) Source #

The timestamp (in seconds since the epoch) of the oldest unfinished task.

tqsLeasedLastHour :: Lens' TaskQueueStats (Maybe Int64) Source #

Number of tasks leased in the last hour.

tqsLeasedLastMinute :: Lens' TaskQueueStats (Maybe Int64) Source #

Number of tasks leased in the last minute.

Tasks

data Tasks Source #

Instances

Eq Tasks Source # 

Methods

(==) :: Tasks -> Tasks -> Bool #

(/=) :: Tasks -> Tasks -> Bool #

Data Tasks Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tasks -> c Tasks #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tasks #

toConstr :: Tasks -> Constr #

dataTypeOf :: Tasks -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tasks) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tasks) #

gmapT :: (forall b. Data b => b -> b) -> Tasks -> Tasks #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tasks -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tasks -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tasks -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tasks -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tasks -> m Tasks #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tasks -> m Tasks #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tasks -> m Tasks #

Show Tasks Source # 

Methods

showsPrec :: Int -> Tasks -> ShowS #

show :: Tasks -> String #

showList :: [Tasks] -> ShowS #

Generic Tasks Source # 

Associated Types

type Rep Tasks :: * -> * #

Methods

from :: Tasks -> Rep Tasks x #

to :: Rep Tasks x -> Tasks #

ToJSON Tasks Source # 
FromJSON Tasks Source # 
type Rep Tasks Source # 
type Rep Tasks = D1 (MetaData "Tasks" "Network.Google.TaskQueue.Types.Product" "gogol-taskqueue-0.3.0-De6GncU4nRo3TG29sWTEtK" False) (C1 (MetaCons "Tasks'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tasKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_tasItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Task])))))

tasks :: Tasks Source #

Creates a value of Tasks with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tasKind :: Lens' Tasks Text Source #

The kind of object returned, a list of tasks.

tasItems :: Lens' Tasks [Task] Source #

The actual list of tasks returned as a result of the lease operation.

Task

data Task Source #

Instances

Eq Task Source # 

Methods

(==) :: Task -> Task -> Bool #

(/=) :: Task -> Task -> Bool #

Data Task Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Task -> c Task #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Task #

toConstr :: Task -> Constr #

dataTypeOf :: Task -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Task) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Task) #

gmapT :: (forall b. Data b => b -> b) -> Task -> Task #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Task -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Task -> r #

gmapQ :: (forall d. Data d => d -> u) -> Task -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Task -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Task -> m Task #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Task -> m Task #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Task -> m Task #

Show Task Source # 

Methods

showsPrec :: Int -> Task -> ShowS #

show :: Task -> String #

showList :: [Task] -> ShowS #

Generic Task Source # 

Associated Types

type Rep Task :: * -> * #

Methods

from :: Task -> Rep Task x #

to :: Rep Task x -> Task #

ToJSON Task Source # 
FromJSON Task Source # 
type Rep Task Source # 

task :: Task Source #

Creates a value of Task with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ttRetryCount :: Lens' Task (Maybe Int32) Source #

The number of leases applied to this task.

ttEnQueueTimestamp :: Lens' Task (Maybe Int64) Source #

Time (in seconds since the epoch) at which the task was enqueued.

ttTag :: Lens' Task (Maybe Text) Source #

Tag for the task, could be used later to lease tasks grouped by a specific tag.

ttKind :: Lens' Task Text Source #

The kind of object returned, in this case set to task.

ttQueueName :: Lens' Task (Maybe Text) Source #

Name of the queue that the task is in.

ttPayloadBase64 :: Lens' Task (Maybe Text) Source #

A bag of bytes which is the task payload. The payload on the JSON side is always Base64 encoded.

ttId :: Lens' Task (Maybe Text) Source #

Name of the task.

ttLeaseTimestamp :: Lens' Task (Maybe Int64) Source #

Time (in seconds since the epoch) at which the task lease will expire. This value is 0 if the task isnt currently leased out to a worker.