{-
   Vikunja API

   # Pagination Every endpoint capable of pagination will return two headers: * `x-pagination-total-pages`: The total number of available pages for this request * `x-pagination-result-count`: The number of items returned for this request. # Rights All endpoints which return a single item (project, task, etc.) - no array - will also return a `x-max-right` header with the max right the user has on this item as an int where `0` is `Read Only`, `1` is `Read & Write` and `2` is `Admin`. This can be used to show or hide ui elements based on the rights the user has. # Errors All errors have an error code and a human-readable error message in addition to the http status code. You should always check for the status code in the response, not only the http status code. Due to limitations in the swagger library we're using for this document, only one error per http status code is documented here. Make sure to check the [error docs](https://vikunja.io/docs/errors/) in Vikunja's documentation for a full list of available error codes. # Authorization **JWT-Auth:** Main authorization method, used for most of the requests. Needs `Authorization: Bearer <jwt-token>`-header to authenticate successfully.  **API Token:** You can create scoped API tokens for your user and use the token to make authenticated requests in the context of that user. The token must be provided via an `Authorization: Bearer <token>` header, similar to jwt auth. See the documentation for the `api` group to manage token creation and revocation.  **BasicAuth:** Only used when requesting tasks via CalDAV. <!-- ReDoc-Inject: <security-definitions> -->

   OpenAPI Version: 3.0.1
   Vikunja API API version: 0.24.6
   Contact: hello@vikunja.io
   Generated by OpenAPI Generator (https://openapi-generator.tech)
-}

{-|
Module : Vikunja.API.Labels
-}

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}

module Vikunja.API.Labels where

import Vikunja.Core
import Vikunja.MimeTypes
import Vikunja.Model as M

import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Typeable, TypeRep, typeOf, typeRep)
import qualified Data.Foldable as P
import qualified Data.Map as Map
import qualified Data.Maybe as P
import qualified Data.Proxy as P (Proxy(..))
import qualified Data.Set as Set
import qualified Data.String as P
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Time as TI
import qualified Network.HTTP.Client.MultipartFormData as NH
import qualified Network.HTTP.Media as ME
import qualified Network.HTTP.Types as NH
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH

import Data.Text (Text)
import GHC.Base ((<|>))

import Prelude ((==),(/=),($), (.),(<$>),(<*>),(>>=),Maybe(..),Bool(..),Char,Double,FilePath,Float,Int,Integer,String,fmap,undefined,mempty,maybe,pure,Monad,Applicative,Functor)
import qualified Prelude as P

-- * Operations


-- ** Labels

-- *** labelsGet

-- | @GET \/labels@
-- 
-- Get all labels a user has access to
-- 
-- Returns all labels which are either created by the user or associated with a task the user has at least read-access to.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
labelsGet
  :: VikunjaRequest LabelsGet MimeNoContent [ModelsLabel] MimeJSON
labelsGet :: VikunjaRequest LabelsGet MimeNoContent [ModelsLabel] MimeJSON
labelsGet =
  Method
-> [ByteString]
-> VikunjaRequest LabelsGet MimeNoContent [ModelsLabel] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/labels"]
    VikunjaRequest LabelsGet MimeNoContent [ModelsLabel] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest LabelsGet MimeNoContent [ModelsLabel] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)

data LabelsGet  

-- | /Optional Param/ "page" - The page number. Used for pagination. If not provided, the first page of results is returned.
instance HasOptionalParam LabelsGet Page where
  applyOptionalParam :: VikunjaRequest LabelsGet contentType res accept
-> Page -> VikunjaRequest LabelsGet contentType res accept
applyOptionalParam VikunjaRequest LabelsGet contentType res accept
req (Page Int
xs) =
    VikunjaRequest LabelsGet contentType res accept
req VikunjaRequest LabelsGet contentType res accept
-> [QueryItem] -> VikunjaRequest LabelsGet contentType res accept
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> [QueryItem] -> VikunjaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "per_page" - The maximum number of items per page. Note this parameter is limited by the configured maximum of items per page.
instance HasOptionalParam LabelsGet PerPage where
  applyOptionalParam :: VikunjaRequest LabelsGet contentType res accept
-> PerPage -> VikunjaRequest LabelsGet contentType res accept
applyOptionalParam VikunjaRequest LabelsGet contentType res accept
req (PerPage Int
xs) =
    VikunjaRequest LabelsGet contentType res accept
req VikunjaRequest LabelsGet contentType res accept
-> [QueryItem] -> VikunjaRequest LabelsGet contentType res accept
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> [QueryItem] -> VikunjaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"per_page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "s" - Search labels by label text.
instance HasOptionalParam LabelsGet S where
  applyOptionalParam :: VikunjaRequest LabelsGet contentType res accept
-> S -> VikunjaRequest LabelsGet contentType res accept
applyOptionalParam VikunjaRequest LabelsGet contentType res accept
req (S Text
xs) =
    VikunjaRequest LabelsGet contentType res accept
req VikunjaRequest LabelsGet contentType res accept
-> [QueryItem] -> VikunjaRequest LabelsGet contentType res accept
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> [QueryItem] -> VikunjaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"s", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces LabelsGet MimeJSON


-- *** labelsIdDelete

-- | @DELETE \/labels\/{id}@
-- 
-- Delete a label
-- 
-- Delete an existing label. The user needs to be the creator of the label to be able to do this.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
labelsIdDelete
  :: Id -- ^ "id" -  Label ID
  -> VikunjaRequest LabelsIdDelete MimeNoContent ModelsLabel MimeJSON
labelsIdDelete :: Id
-> VikunjaRequest LabelsIdDelete MimeNoContent ModelsLabel MimeJSON
labelsIdDelete (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest LabelsIdDelete MimeNoContent ModelsLabel MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/labels/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    VikunjaRequest LabelsIdDelete MimeNoContent ModelsLabel MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest LabelsIdDelete MimeNoContent ModelsLabel MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)

data LabelsIdDelete  
-- | @application/json@
instance Produces LabelsIdDelete MimeJSON


-- *** labelsIdGet

-- | @GET \/labels\/{id}@
-- 
-- Gets one label
-- 
-- Returns one label by its ID.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
labelsIdGet
  :: Id -- ^ "id" -  Label ID
  -> VikunjaRequest LabelsIdGet MimeNoContent ModelsLabel MimeJSON
labelsIdGet :: Id -> VikunjaRequest LabelsIdGet MimeNoContent ModelsLabel MimeJSON
labelsIdGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest LabelsIdGet MimeNoContent ModelsLabel MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/labels/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    VikunjaRequest LabelsIdGet MimeNoContent ModelsLabel MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest LabelsIdGet MimeNoContent ModelsLabel MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)

data LabelsIdGet  
-- | @application/json@
instance Produces LabelsIdGet MimeJSON


-- *** labelsIdPut

-- | @PUT \/labels\/{id}@
-- 
-- Update a label
-- 
-- Update an existing label. The user needs to be the creator of the label to be able to do this.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
labelsIdPut
  :: (Consumes LabelsIdPut MimeJSON, MimeRender MimeJSON ModelsLabel)
  => ModelsLabel -- ^ "label" -  The label object
  -> Id -- ^ "id" -  Label ID
  -> VikunjaRequest LabelsIdPut MimeJSON ModelsLabel MimeJSON
labelsIdPut :: ModelsLabel
-> Id -> VikunjaRequest LabelsIdPut MimeJSON ModelsLabel MimeJSON
labelsIdPut ModelsLabel
label (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest LabelsIdPut MimeJSON ModelsLabel MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/labels/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    VikunjaRequest LabelsIdPut MimeJSON ModelsLabel MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest LabelsIdPut MimeJSON ModelsLabel MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)
    VikunjaRequest LabelsIdPut MimeJSON ModelsLabel MimeJSON
-> ModelsLabel
-> VikunjaRequest LabelsIdPut MimeJSON ModelsLabel MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
VikunjaRequest req contentType res accept
-> param -> VikunjaRequest req contentType res accept
`setBodyParam` ModelsLabel
label

data LabelsIdPut 

-- | /Body Param/ "label" - The label object
instance HasBodyParam LabelsIdPut ModelsLabel 

-- | @application/json@
instance Consumes LabelsIdPut MimeJSON

-- | @application/json@
instance Produces LabelsIdPut MimeJSON


-- *** labelsPut

-- | @PUT \/labels@
-- 
-- Create a label
-- 
-- Creates a new label.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
labelsPut
  :: (Consumes LabelsPut MimeJSON, MimeRender MimeJSON ModelsLabel)
  => ModelsLabel -- ^ "label" -  The label object
  -> VikunjaRequest LabelsPut MimeJSON ModelsLabel MimeJSON
labelsPut :: ModelsLabel
-> VikunjaRequest LabelsPut MimeJSON ModelsLabel MimeJSON
labelsPut ModelsLabel
label =
  Method
-> [ByteString]
-> VikunjaRequest LabelsPut MimeJSON ModelsLabel MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/labels"]
    VikunjaRequest LabelsPut MimeJSON ModelsLabel MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest LabelsPut MimeJSON ModelsLabel MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)
    VikunjaRequest LabelsPut MimeJSON ModelsLabel MimeJSON
-> ModelsLabel
-> VikunjaRequest LabelsPut MimeJSON ModelsLabel MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
VikunjaRequest req contentType res accept
-> param -> VikunjaRequest req contentType res accept
`setBodyParam` ModelsLabel
label

data LabelsPut 

-- | /Body Param/ "label" - The label object
instance HasBodyParam LabelsPut ModelsLabel 

-- | @application/json@
instance Consumes LabelsPut MimeJSON

-- | @application/json@
instance Produces LabelsPut MimeJSON


-- *** tasksTaskIDLabelsBulkPost

-- | @POST \/tasks\/{taskID}\/labels\/bulk@
-- 
-- Update all labels on a task.
-- 
-- Updates all labels on a task. Every label which is not passed but exists on the task will be deleted. Every label which does not exist on the task will be added. All labels which are passed and already exist on the task won't be touched.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDLabelsBulkPost
  :: (Consumes TasksTaskIDLabelsBulkPost MimeJSON, MimeRender MimeJSON ModelsLabelTaskBulk)
  => ModelsLabelTaskBulk -- ^ "label" -  The array of labels
  -> TaskId -- ^ "taskId" -  Task ID
  -> VikunjaRequest TasksTaskIDLabelsBulkPost MimeJSON ModelsLabelTaskBulk MimeJSON
tasksTaskIDLabelsBulkPost :: ModelsLabelTaskBulk
-> TaskId
-> VikunjaRequest
     TasksTaskIDLabelsBulkPost MimeJSON ModelsLabelTaskBulk MimeJSON
tasksTaskIDLabelsBulkPost ModelsLabelTaskBulk
label (TaskId Int
taskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDLabelsBulkPost MimeJSON ModelsLabelTaskBulk MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/tasks/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
taskId,ByteString
"/labels/bulk"]
    VikunjaRequest
  TasksTaskIDLabelsBulkPost MimeJSON ModelsLabelTaskBulk MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDLabelsBulkPost MimeJSON ModelsLabelTaskBulk MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)
    VikunjaRequest
  TasksTaskIDLabelsBulkPost MimeJSON ModelsLabelTaskBulk MimeJSON
-> ModelsLabelTaskBulk
-> VikunjaRequest
     TasksTaskIDLabelsBulkPost MimeJSON ModelsLabelTaskBulk MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
VikunjaRequest req contentType res accept
-> param -> VikunjaRequest req contentType res accept
`setBodyParam` ModelsLabelTaskBulk
label

data TasksTaskIDLabelsBulkPost 

-- | /Body Param/ "label" - The array of labels
instance HasBodyParam TasksTaskIDLabelsBulkPost ModelsLabelTaskBulk 

-- | @application/json@
instance Consumes TasksTaskIDLabelsBulkPost MimeJSON

-- | @application/json@
instance Produces TasksTaskIDLabelsBulkPost MimeJSON


-- *** tasksTaskLabelsGet

-- | @GET \/tasks\/{task}\/labels@
-- 
-- Get all labels on a task
-- 
-- Returns all labels which are assicociated with a given task.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskLabelsGet
  :: Task -- ^ "task" -  Task ID
  -> VikunjaRequest TasksTaskLabelsGet MimeNoContent [ModelsLabel] MimeJSON
tasksTaskLabelsGet :: Task
-> VikunjaRequest
     TasksTaskLabelsGet MimeNoContent [ModelsLabel] MimeJSON
tasksTaskLabelsGet (Task Int
task) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskLabelsGet MimeNoContent [ModelsLabel] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/tasks/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
task,ByteString
"/labels"]
    VikunjaRequest
  TasksTaskLabelsGet MimeNoContent [ModelsLabel] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskLabelsGet MimeNoContent [ModelsLabel] MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)

data TasksTaskLabelsGet  

-- | /Optional Param/ "page" - The page number. Used for pagination. If not provided, the first page of results is returned.
instance HasOptionalParam TasksTaskLabelsGet Page where
  applyOptionalParam :: VikunjaRequest TasksTaskLabelsGet contentType res accept
-> Page -> VikunjaRequest TasksTaskLabelsGet contentType res accept
applyOptionalParam VikunjaRequest TasksTaskLabelsGet contentType res accept
req (Page Int
xs) =
    VikunjaRequest TasksTaskLabelsGet contentType res accept
req VikunjaRequest TasksTaskLabelsGet contentType res accept
-> [QueryItem]
-> VikunjaRequest TasksTaskLabelsGet contentType res accept
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> [QueryItem] -> VikunjaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "per_page" - The maximum number of items per page. Note this parameter is limited by the configured maximum of items per page.
instance HasOptionalParam TasksTaskLabelsGet PerPage where
  applyOptionalParam :: VikunjaRequest TasksTaskLabelsGet contentType res accept
-> PerPage
-> VikunjaRequest TasksTaskLabelsGet contentType res accept
applyOptionalParam VikunjaRequest TasksTaskLabelsGet contentType res accept
req (PerPage Int
xs) =
    VikunjaRequest TasksTaskLabelsGet contentType res accept
req VikunjaRequest TasksTaskLabelsGet contentType res accept
-> [QueryItem]
-> VikunjaRequest TasksTaskLabelsGet contentType res accept
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> [QueryItem] -> VikunjaRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"per_page", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | /Optional Param/ "s" - Search labels by label text.
instance HasOptionalParam TasksTaskLabelsGet S where
  applyOptionalParam :: VikunjaRequest TasksTaskLabelsGet contentType res accept
-> S -> VikunjaRequest TasksTaskLabelsGet contentType res accept
applyOptionalParam VikunjaRequest TasksTaskLabelsGet contentType res accept
req (S Text
xs) =
    VikunjaRequest TasksTaskLabelsGet contentType res accept
req VikunjaRequest TasksTaskLabelsGet contentType res accept
-> [QueryItem]
-> VikunjaRequest TasksTaskLabelsGet contentType res accept
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> [QueryItem] -> VikunjaRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"s", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces TasksTaskLabelsGet MimeJSON


-- *** tasksTaskLabelsLabelDelete

-- | @DELETE \/tasks\/{task}\/labels\/{label}@
-- 
-- Remove a label from a task
-- 
-- Remove a label from a task. The user needs to have write-access to the project to be able do this.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskLabelsLabelDelete
  :: Task -- ^ "task" -  Task ID
  -> Label -- ^ "label" -  Label ID
  -> VikunjaRequest TasksTaskLabelsLabelDelete MimeNoContent ModelsMessage MimeJSON
tasksTaskLabelsLabelDelete :: Task
-> Label
-> VikunjaRequest
     TasksTaskLabelsLabelDelete MimeNoContent ModelsMessage MimeJSON
tasksTaskLabelsLabelDelete (Task Int
task) (Label Int
label) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskLabelsLabelDelete MimeNoContent ModelsMessage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/tasks/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
task,ByteString
"/labels/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
label]
    VikunjaRequest
  TasksTaskLabelsLabelDelete MimeNoContent ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskLabelsLabelDelete MimeNoContent ModelsMessage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)

data TasksTaskLabelsLabelDelete  
-- | @application/json@
instance Produces TasksTaskLabelsLabelDelete MimeJSON


-- *** tasksTaskLabelsPut

-- | @PUT \/tasks\/{task}\/labels@
-- 
-- Add a label to a task
-- 
-- Add a label to a task. The user needs to have write-access to the project to be able do this.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskLabelsPut
  :: (Consumes TasksTaskLabelsPut MimeJSON, MimeRender MimeJSON ModelsLabelTask)
  => ModelsLabelTask -- ^ "label" -  The label object
  -> Task -- ^ "task" -  Task ID
  -> VikunjaRequest TasksTaskLabelsPut MimeJSON ModelsLabelTask MimeJSON
tasksTaskLabelsPut :: ModelsLabelTask
-> Task
-> VikunjaRequest
     TasksTaskLabelsPut MimeJSON ModelsLabelTask MimeJSON
tasksTaskLabelsPut ModelsLabelTask
label (Task Int
task) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskLabelsPut MimeJSON ModelsLabelTask MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/tasks/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
task,ByteString
"/labels"]
    VikunjaRequest TasksTaskLabelsPut MimeJSON ModelsLabelTask MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskLabelsPut MimeJSON ModelsLabelTask MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)
    VikunjaRequest TasksTaskLabelsPut MimeJSON ModelsLabelTask MimeJSON
-> ModelsLabelTask
-> VikunjaRequest
     TasksTaskLabelsPut MimeJSON ModelsLabelTask MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
VikunjaRequest req contentType res accept
-> param -> VikunjaRequest req contentType res accept
`setBodyParam` ModelsLabelTask
label

data TasksTaskLabelsPut 

-- | /Body Param/ "label" - The label object
instance HasBodyParam TasksTaskLabelsPut ModelsLabelTask 

-- | @application/json@
instance Consumes TasksTaskLabelsPut MimeJSON

-- | @application/json@
instance Produces TasksTaskLabelsPut MimeJSON