{-
   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.Task
-}

{-# 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.Task 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


-- ** Task

-- *** kindIdReactionsDeletePost

-- | @POST \/{kind}\/{id}\/reactions\/delete@
-- 
-- Removes the user's reaction
-- 
-- Removes the reaction of that user on that entity.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
kindIdReactionsDeletePost
  :: (Consumes KindIdReactionsDeletePost MimeJSON, MimeRender MimeJSON ModelsReaction)
  => ModelsReaction -- ^ "project" -  The reaction you want to add to the entity.
  -> Id -- ^ "id" -  Entity ID
  -> Kind -- ^ "kind" -  The kind of the entity. Can be either `tasks` or `comments` for task comments
  -> VikunjaRequest KindIdReactionsDeletePost MimeJSON ModelsMessage MimeJSON
kindIdReactionsDeletePost :: ModelsReaction
-> Id
-> Kind
-> VikunjaRequest
     KindIdReactionsDeletePost MimeJSON ModelsMessage MimeJSON
kindIdReactionsDeletePost ModelsReaction
project (Id Int
id) (Kind Int
kind) =
  Method
-> [ByteString]
-> VikunjaRequest
     KindIdReactionsDeletePost MimeJSON ModelsMessage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
kind,ByteString
"/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id,ByteString
"/reactions/delete"]
    VikunjaRequest
  KindIdReactionsDeletePost MimeJSON ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     KindIdReactionsDeletePost MimeJSON 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)
    VikunjaRequest
  KindIdReactionsDeletePost MimeJSON ModelsMessage MimeJSON
-> ModelsReaction
-> VikunjaRequest
     KindIdReactionsDeletePost MimeJSON ModelsMessage 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` ModelsReaction
project

data KindIdReactionsDeletePost 

-- | /Body Param/ "project" - The reaction you want to add to the entity.
instance HasBodyParam KindIdReactionsDeletePost ModelsReaction 

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

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


-- *** kindIdReactionsGet

-- | @GET \/{kind}\/{id}\/reactions@
-- 
-- Get all reactions for an entity
-- 
-- Returns all reactions for an entity
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
kindIdReactionsGet
  :: Id -- ^ "id" -  Entity ID
  -> Kind -- ^ "kind" -  The kind of the entity. Can be either `tasks` or `comments` for task comments
  -> VikunjaRequest KindIdReactionsGet MimeNoContent [Map.Map String [UserUser]] MimeJSON
kindIdReactionsGet :: Id
-> Kind
-> VikunjaRequest
     KindIdReactionsGet MimeNoContent [Map String [UserUser]] MimeJSON
kindIdReactionsGet (Id Int
id) (Kind Int
kind) =
  Method
-> [ByteString]
-> VikunjaRequest
     KindIdReactionsGet MimeNoContent [Map String [UserUser]] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
kind,ByteString
"/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id,ByteString
"/reactions"]
    VikunjaRequest
  KindIdReactionsGet MimeNoContent [Map String [UserUser]] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     KindIdReactionsGet MimeNoContent [Map String [UserUser]] 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 KindIdReactionsGet  
-- | @application/json@
instance Produces KindIdReactionsGet MimeJSON


-- *** kindIdReactionsPut

-- | @PUT \/{kind}\/{id}\/reactions@
-- 
-- Add a reaction to an entity
-- 
-- Add a reaction to an entity. Will do nothing if the reaction already exists.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
kindIdReactionsPut
  :: (Consumes KindIdReactionsPut MimeJSON, MimeRender MimeJSON ModelsReaction)
  => ModelsReaction -- ^ "project" -  The reaction you want to add to the entity.
  -> Id -- ^ "id" -  Entity ID
  -> Kind -- ^ "kind" -  The kind of the entity. Can be either `tasks` or `comments` for task comments
  -> VikunjaRequest KindIdReactionsPut MimeJSON ModelsReaction MimeJSON
kindIdReactionsPut :: ModelsReaction
-> Id
-> Kind
-> VikunjaRequest
     KindIdReactionsPut MimeJSON ModelsReaction MimeJSON
kindIdReactionsPut ModelsReaction
project (Id Int
id) (Kind Int
kind) =
  Method
-> [ByteString]
-> VikunjaRequest
     KindIdReactionsPut MimeJSON ModelsReaction MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
kind,ByteString
"/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id,ByteString
"/reactions"]
    VikunjaRequest KindIdReactionsPut MimeJSON ModelsReaction MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     KindIdReactionsPut MimeJSON ModelsReaction 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 KindIdReactionsPut MimeJSON ModelsReaction MimeJSON
-> ModelsReaction
-> VikunjaRequest
     KindIdReactionsPut MimeJSON ModelsReaction 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` ModelsReaction
project

data KindIdReactionsPut 

-- | /Body Param/ "project" - The reaction you want to add to the entity.
instance HasBodyParam KindIdReactionsPut ModelsReaction 

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

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


-- *** projectsIdTasksPut

-- | @PUT \/projects\/{id}\/tasks@
-- 
-- Create a task
-- 
-- Inserts a task into a project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdTasksPut
  :: (Consumes ProjectsIdTasksPut MimeJSON, MimeRender MimeJSON ModelsTask)
  => ModelsTask -- ^ "task" -  The task object
  -> Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdTasksPut MimeJSON ModelsTask MimeJSON
projectsIdTasksPut :: ModelsTask
-> Id
-> VikunjaRequest ProjectsIdTasksPut MimeJSON ModelsTask MimeJSON
projectsIdTasksPut ModelsTask
task (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest ProjectsIdTasksPut MimeJSON ModelsTask MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/projects/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id,ByteString
"/tasks"]
    VikunjaRequest ProjectsIdTasksPut MimeJSON ModelsTask MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest ProjectsIdTasksPut MimeJSON ModelsTask 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 ProjectsIdTasksPut MimeJSON ModelsTask MimeJSON
-> ModelsTask
-> VikunjaRequest ProjectsIdTasksPut MimeJSON ModelsTask 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` ModelsTask
task

data ProjectsIdTasksPut 

-- | /Body Param/ "task" - The task object
instance HasBodyParam ProjectsIdTasksPut ModelsTask 

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

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


-- *** projectsIdViewsViewTasksGet

-- | @GET \/projects\/{id}\/views\/{view}\/tasks@
-- 
-- Get tasks in a project
-- 
-- Returns all tasks for the current project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdViewsViewTasksGet
  :: Id -- ^ "id" -  The project ID.
  -> View -- ^ "view" -  The project view ID.
  -> VikunjaRequest ProjectsIdViewsViewTasksGet MimeNoContent [ModelsTask] MimeJSON
projectsIdViewsViewTasksGet :: Id
-> View
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet MimeNoContent [ModelsTask] MimeJSON
projectsIdViewsViewTasksGet (Id Int
id) (View Int
view) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet MimeNoContent [ModelsTask] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/projects/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id,ByteString
"/views/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
view,ByteString
"/tasks"]
    VikunjaRequest
  ProjectsIdViewsViewTasksGet MimeNoContent [ModelsTask] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet MimeNoContent [ModelsTask] 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 ProjectsIdViewsViewTasksGet  

-- | /Optional Param/ "page" - The page number. Used for pagination. If not provided, the first page of results is returned.
instance HasOptionalParam ProjectsIdViewsViewTasksGet Page where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> Page
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (Page Int
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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 ProjectsIdViewsViewTasksGet PerPage where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> PerPage
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (PerPage Int
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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 tasks by task text.
instance HasOptionalParam ProjectsIdViewsViewTasksGet S where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> S
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (S Text
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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)

-- | /Optional Param/ "sort_by" - The sorting parameter. You can pass this multiple times to get the tasks ordered by multiple different parametes, along with `order_by`. Possible values to sort by are `id`, `title`, `description`, `done`, `done_at`, `due_date`, `created_by_id`, `project_id`, `repeat_after`, `priority`, `start_date`, `end_date`, `hex_color`, `percent_done`, `uid`, `created`, `updated`. Default is `id`.
instance HasOptionalParam ProjectsIdViewsViewTasksGet SortBy where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> SortBy
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (SortBy Text
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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
"sort_by", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "order_by" - The ordering parameter. Possible values to order by are `asc` or `desc`. Default is `asc`.
instance HasOptionalParam ProjectsIdViewsViewTasksGet OrderBy where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> OrderBy
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (OrderBy Text
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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
"order_by", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "filter" - The filter query to match tasks by. Check out https://vikunja.io/docs/filters for a full explanation of the feature.
instance HasOptionalParam ProjectsIdViewsViewTasksGet Filter where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> Filter
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (Filter Text
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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
"filter", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "filter_timezone" - The time zone which should be used for date match (statements like 
instance HasOptionalParam ProjectsIdViewsViewTasksGet FilterTimezone where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> FilterTimezone
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (FilterTimezone Text
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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
"filter_timezone", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "filter_include_nulls" - If set to true the result will include filtered fields whose value is set to `null`. Available values are `true` or `false`. Defaults to `false`.
instance HasOptionalParam ProjectsIdViewsViewTasksGet FilterIncludeNulls where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> FilterIncludeNulls
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (FilterIncludeNulls Text
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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
"filter_include_nulls", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "expand" - If set to `subtasks`, Vikunja will fetch only tasks which do not have subtasks and then in a second step, will fetch all of these subtasks. This may result in more tasks than the pagination limit being returned, but all subtasks will be present in the response. You can only set this to `subtasks`.
instance HasOptionalParam ProjectsIdViewsViewTasksGet Expand where
  applyOptionalParam :: VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> Expand
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req (Expand Text
xs) =
    VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
req VikunjaRequest ProjectsIdViewsViewTasksGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     ProjectsIdViewsViewTasksGet 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
"expand", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ProjectsIdViewsViewTasksGet MimeJSON


-- *** projectsProjectViewsViewBucketsBucketTasksPost

-- | @POST \/projects\/{project}\/views\/{view}\/buckets\/{bucket}\/tasks@
-- 
-- Update a task bucket
-- 
-- Updates a task in a bucket
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectViewsViewBucketsBucketTasksPost
  :: (Consumes ProjectsProjectViewsViewBucketsBucketTasksPost MimeJSON, MimeRender MimeJSON ModelsTaskBucket)
  => ModelsTaskBucket -- ^ "taskBucket" -  The id of the task you want to move into the bucket.
  -> Project -- ^ "project" -  Project ID
  -> View -- ^ "view" -  Project View ID
  -> Bucket -- ^ "bucket" -  Bucket ID
  -> VikunjaRequest ProjectsProjectViewsViewBucketsBucketTasksPost MimeJSON ModelsTaskBucket MimeJSON
projectsProjectViewsViewBucketsBucketTasksPost :: ModelsTaskBucket
-> Project
-> View
-> Bucket
-> VikunjaRequest
     ProjectsProjectViewsViewBucketsBucketTasksPost
     MimeJSON
     ModelsTaskBucket
     MimeJSON
projectsProjectViewsViewBucketsBucketTasksPost ModelsTaskBucket
taskBucket (Project Int
project) (View Int
view) (Bucket Int
bucket) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectViewsViewBucketsBucketTasksPost
     MimeJSON
     ModelsTaskBucket
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/projects/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
project,ByteString
"/views/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
view,ByteString
"/buckets/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
bucket,ByteString
"/tasks"]
    VikunjaRequest
  ProjectsProjectViewsViewBucketsBucketTasksPost
  MimeJSON
  ModelsTaskBucket
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectViewsViewBucketsBucketTasksPost
     MimeJSON
     ModelsTaskBucket
     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
  ProjectsProjectViewsViewBucketsBucketTasksPost
  MimeJSON
  ModelsTaskBucket
  MimeJSON
-> ModelsTaskBucket
-> VikunjaRequest
     ProjectsProjectViewsViewBucketsBucketTasksPost
     MimeJSON
     ModelsTaskBucket
     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` ModelsTaskBucket
taskBucket

data ProjectsProjectViewsViewBucketsBucketTasksPost 

-- | /Body Param/ "taskBucket" - The id of the task you want to move into the bucket.
instance HasBodyParam ProjectsProjectViewsViewBucketsBucketTasksPost ModelsTaskBucket 

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

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


-- *** tasksAllGet

-- | @GET \/tasks\/all@
-- 
-- Get tasks
-- 
-- Returns all tasks on any project the user has access to.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksAllGet
  :: VikunjaRequest TasksAllGet MimeNoContent [ModelsTask] MimeJSON
tasksAllGet :: VikunjaRequest TasksAllGet MimeNoContent [ModelsTask] MimeJSON
tasksAllGet =
  Method
-> [ByteString]
-> VikunjaRequest TasksAllGet MimeNoContent [ModelsTask] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/tasks/all"]
    VikunjaRequest TasksAllGet MimeNoContent [ModelsTask] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest TasksAllGet MimeNoContent [ModelsTask] 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 TasksAllGet  

-- | /Optional Param/ "page" - The page number. Used for pagination. If not provided, the first page of results is returned.
instance HasOptionalParam TasksAllGet Page where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> Page -> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (Page Int
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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 TasksAllGet PerPage where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> PerPage -> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (PerPage Int
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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 tasks by task text.
instance HasOptionalParam TasksAllGet S where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> S -> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (S Text
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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)

-- | /Optional Param/ "sort_by" - The sorting parameter. You can pass this multiple times to get the tasks ordered by multiple different parametes, along with `order_by`. Possible values to sort by are `id`, `title`, `description`, `done`, `done_at`, `due_date`, `created_by_id`, `project_id`, `repeat_after`, `priority`, `start_date`, `end_date`, `hex_color`, `percent_done`, `uid`, `created`, `updated`. Default is `id`.
instance HasOptionalParam TasksAllGet SortBy where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> SortBy -> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (SortBy Text
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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
"sort_by", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "order_by" - The ordering parameter. Possible values to order by are `asc` or `desc`. Default is `asc`.
instance HasOptionalParam TasksAllGet OrderBy where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> OrderBy -> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (OrderBy Text
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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
"order_by", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "filter" - The filter query to match tasks by. Check out https://vikunja.io/docs/filters for a full explanation of the feature.
instance HasOptionalParam TasksAllGet Filter where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> Filter -> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (Filter Text
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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
"filter", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "filter_timezone" - The time zone which should be used for date match (statements like 
instance HasOptionalParam TasksAllGet FilterTimezone where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> FilterTimezone
-> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (FilterTimezone Text
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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
"filter_timezone", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "filter_include_nulls" - If set to true the result will include filtered fields whose value is set to `null`. Available values are `true` or `false`. Defaults to `false`.
instance HasOptionalParam TasksAllGet FilterIncludeNulls where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> FilterIncludeNulls
-> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (FilterIncludeNulls Text
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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
"filter_include_nulls", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "expand" - If set to `subtasks`, Vikunja will fetch only tasks which do not have subtasks and then in a second step, will fetch all of these subtasks. This may result in more tasks than the pagination limit being returned, but all subtasks will be present in the response. You can only set this to `subtasks`.
instance HasOptionalParam TasksAllGet Expand where
  applyOptionalParam :: VikunjaRequest TasksAllGet contentType res accept
-> Expand -> VikunjaRequest TasksAllGet contentType res accept
applyOptionalParam VikunjaRequest TasksAllGet contentType res accept
req (Expand Text
xs) =
    VikunjaRequest TasksAllGet contentType res accept
req VikunjaRequest TasksAllGet contentType res accept
-> [QueryItem] -> VikunjaRequest TasksAllGet 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
"expand", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces TasksAllGet MimeJSON


-- *** tasksBulkPost

-- | @POST \/tasks\/bulk@
-- 
-- Update a bunch of tasks at once
-- 
-- Updates a bunch of tasks at once. This includes marking them as done. Note: although you could supply another ID, it will be ignored. Use task_ids instead.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksBulkPost
  :: (Consumes TasksBulkPost MimeJSON, MimeRender MimeJSON ModelsBulkTask)
  => ModelsBulkTask -- ^ "task" -  The task object. Looks like a normal task, the only difference is it uses an array of project_ids to update.
  -> VikunjaRequest TasksBulkPost MimeJSON ModelsTask MimeJSON
tasksBulkPost :: ModelsBulkTask
-> VikunjaRequest TasksBulkPost MimeJSON ModelsTask MimeJSON
tasksBulkPost ModelsBulkTask
task =
  Method
-> [ByteString]
-> VikunjaRequest TasksBulkPost MimeJSON ModelsTask MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/tasks/bulk"]
    VikunjaRequest TasksBulkPost MimeJSON ModelsTask MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest TasksBulkPost MimeJSON ModelsTask 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 TasksBulkPost MimeJSON ModelsTask MimeJSON
-> ModelsBulkTask
-> VikunjaRequest TasksBulkPost MimeJSON ModelsTask 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` ModelsBulkTask
task

data TasksBulkPost 

-- | /Body Param/ "task" - The task object. Looks like a normal task, the only difference is it uses an array of project_ids to update.
instance HasBodyParam TasksBulkPost ModelsBulkTask 

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

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


-- *** tasksIdAttachmentsAttachmentIDDelete

-- | @DELETE \/tasks\/{id}\/attachments\/{attachmentID}@
-- 
-- Delete an attachment
-- 
-- Delete an attachment.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdAttachmentsAttachmentIDDelete
  :: Id -- ^ "id" -  Task ID
  -> AttachmentId -- ^ "attachmentId" -  Attachment ID
  -> VikunjaRequest TasksIdAttachmentsAttachmentIDDelete MimeNoContent ModelsMessage MimeJSON
tasksIdAttachmentsAttachmentIDDelete :: Id
-> AttachmentId
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
tasksIdAttachmentsAttachmentIDDelete (Id Int
id) (AttachmentId Int
attachmentId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDDelete
     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
id,ByteString
"/attachments/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
attachmentId]
    VikunjaRequest
  TasksIdAttachmentsAttachmentIDDelete
  MimeNoContent
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDDelete
     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 TasksIdAttachmentsAttachmentIDDelete  
-- | @application/json@
instance Produces TasksIdAttachmentsAttachmentIDDelete MimeJSON


-- *** tasksIdAttachmentsAttachmentIDGet

-- | @GET \/tasks\/{id}\/attachments\/{attachmentID}@
-- 
-- Get one attachment.
-- 
-- Get one attachment for download. **Returns json on error.**
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdAttachmentsAttachmentIDGet
  :: Id -- ^ "id" -  Task ID
  -> AttachmentId -- ^ "attachmentId" -  Attachment ID
  -> VikunjaRequest TasksIdAttachmentsAttachmentIDGet MimeNoContent FilePath MimeOctetStream
tasksIdAttachmentsAttachmentIDGet :: Id
-> AttachmentId
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDGet
     MimeNoContent
     String
     MimeOctetStream
tasksIdAttachmentsAttachmentIDGet (Id Int
id) (AttachmentId Int
attachmentId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDGet
     MimeNoContent
     String
     MimeOctetStream
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
id,ByteString
"/attachments/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
attachmentId]
    VikunjaRequest
  TasksIdAttachmentsAttachmentIDGet
  MimeNoContent
  String
  MimeOctetStream
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDGet
     MimeNoContent
     String
     MimeOctetStream
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 TasksIdAttachmentsAttachmentIDGet  

-- | /Optional Param/ "preview_size" - The size of the preview image. Can be sm = 100px, md = 200px, lg = 400px or xl = 800px. If provided, a preview image will be returned if the attachment is an image.
instance HasOptionalParam TasksIdAttachmentsAttachmentIDGet PreviewSize where
  applyOptionalParam :: VikunjaRequest
  TasksIdAttachmentsAttachmentIDGet contentType res accept
-> PreviewSize
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDGet contentType res accept
applyOptionalParam VikunjaRequest
  TasksIdAttachmentsAttachmentIDGet contentType res accept
req (PreviewSize Text
xs) =
    VikunjaRequest
  TasksIdAttachmentsAttachmentIDGet contentType res accept
req VikunjaRequest
  TasksIdAttachmentsAttachmentIDGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     TasksIdAttachmentsAttachmentIDGet 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
"preview_size", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
-- | @application/octet-stream@
instance Produces TasksIdAttachmentsAttachmentIDGet MimeOctetStream


-- *** tasksIdAttachmentsGet

-- | @GET \/tasks\/{id}\/attachments@
-- 
-- Get  all attachments for one task.
-- 
-- Get all task attachments for one task.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdAttachmentsGet
  :: Id -- ^ "id" -  Task ID
  -> VikunjaRequest TasksIdAttachmentsGet MimeNoContent [ModelsTaskAttachment] MimeJSON
tasksIdAttachmentsGet :: Id
-> VikunjaRequest
     TasksIdAttachmentsGet MimeNoContent [ModelsTaskAttachment] MimeJSON
tasksIdAttachmentsGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksIdAttachmentsGet MimeNoContent [ModelsTaskAttachment] 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
id,ByteString
"/attachments"]
    VikunjaRequest
  TasksIdAttachmentsGet MimeNoContent [ModelsTaskAttachment] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksIdAttachmentsGet MimeNoContent [ModelsTaskAttachment] 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 TasksIdAttachmentsGet  

-- | /Optional Param/ "page" - The page number. Used for pagination. If not provided, the first page of results is returned.
instance HasOptionalParam TasksIdAttachmentsGet Page where
  applyOptionalParam :: VikunjaRequest TasksIdAttachmentsGet contentType res accept
-> Page
-> VikunjaRequest TasksIdAttachmentsGet contentType res accept
applyOptionalParam VikunjaRequest TasksIdAttachmentsGet contentType res accept
req (Page Int
xs) =
    VikunjaRequest TasksIdAttachmentsGet contentType res accept
req VikunjaRequest TasksIdAttachmentsGet contentType res accept
-> [QueryItem]
-> VikunjaRequest TasksIdAttachmentsGet 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 TasksIdAttachmentsGet PerPage where
  applyOptionalParam :: VikunjaRequest TasksIdAttachmentsGet contentType res accept
-> PerPage
-> VikunjaRequest TasksIdAttachmentsGet contentType res accept
applyOptionalParam VikunjaRequest TasksIdAttachmentsGet contentType res accept
req (PerPage Int
xs) =
    VikunjaRequest TasksIdAttachmentsGet contentType res accept
req VikunjaRequest TasksIdAttachmentsGet contentType res accept
-> [QueryItem]
-> VikunjaRequest TasksIdAttachmentsGet 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)
-- | @application/json@
instance Produces TasksIdAttachmentsGet MimeJSON


-- *** tasksIdAttachmentsPut

-- | @PUT \/tasks\/{id}\/attachments@
-- 
-- Upload a task attachment
-- 
-- Upload a task attachment. You can pass multiple files with the files form param.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdAttachmentsPut
  :: (Consumes TasksIdAttachmentsPut MimeMultipartFormData)
  => Files -- ^ "files" -  The file, as multipart form file. You can pass multiple.
  -> Id -- ^ "id" -  Task ID
  -> VikunjaRequest TasksIdAttachmentsPut MimeMultipartFormData ModelsMessage MimeJSON
tasksIdAttachmentsPut :: Files
-> Id
-> VikunjaRequest
     TasksIdAttachmentsPut MimeMultipartFormData ModelsMessage MimeJSON
tasksIdAttachmentsPut (Files Text
files) (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksIdAttachmentsPut MimeMultipartFormData ModelsMessage 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
id,ByteString
"/attachments"]
    VikunjaRequest
  TasksIdAttachmentsPut MimeMultipartFormData ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksIdAttachmentsPut MimeMultipartFormData 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)
    VikunjaRequest
  TasksIdAttachmentsPut MimeMultipartFormData ModelsMessage MimeJSON
-> Part
-> VikunjaRequest
     TasksIdAttachmentsPut MimeMultipartFormData ModelsMessage MimeJSON
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> Part -> VikunjaRequest req contentType res accept
`_addMultiFormPart` Text -> ByteString -> Part
forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
NH.partLBS Text
"files" (MimeMultipartFormData -> Text -> ByteString
forall mtype x. MimeRender mtype x => mtype -> x -> ByteString
mimeRender' MimeMultipartFormData
MimeMultipartFormData Text
files)

data TasksIdAttachmentsPut  

-- | @multipart/form-data@
instance Consumes TasksIdAttachmentsPut MimeMultipartFormData

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


-- *** tasksIdDelete

-- | @DELETE \/tasks\/{id}@
-- 
-- Delete a task
-- 
-- Deletes a task from a project. This does not mean \"mark it done\".
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdDelete
  :: Id -- ^ "id" -  Task ID
  -> VikunjaRequest TasksIdDelete MimeNoContent ModelsMessage MimeJSON
tasksIdDelete :: Id
-> VikunjaRequest
     TasksIdDelete MimeNoContent ModelsMessage MimeJSON
tasksIdDelete (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksIdDelete 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
id]
    VikunjaRequest TasksIdDelete MimeNoContent ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksIdDelete 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 TasksIdDelete  
-- | @application/json@
instance Produces TasksIdDelete MimeJSON


-- *** tasksIdGet

-- | @GET \/tasks\/{id}@
-- 
-- Get one task
-- 
-- Returns one task by its ID
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdGet
  :: Id -- ^ "id" -  The task ID
  -> VikunjaRequest TasksIdGet MimeNoContent ModelsTask MimeJSON
tasksIdGet :: Id -> VikunjaRequest TasksIdGet MimeNoContent ModelsTask MimeJSON
tasksIdGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest TasksIdGet MimeNoContent ModelsTask 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
id]
    VikunjaRequest TasksIdGet MimeNoContent ModelsTask MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest TasksIdGet MimeNoContent ModelsTask 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 TasksIdGet  
-- | @application/json@
instance Produces TasksIdGet MimeJSON


-- *** tasksIdPositionPost

-- | @POST \/tasks\/{id}\/position@
-- 
-- Updates a task position
-- 
-- Updates a task position.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdPositionPost
  :: (Consumes TasksIdPositionPost MimeJSON, MimeRender MimeJSON ModelsTaskPosition)
  => ModelsTaskPosition -- ^ "view" -  The task position with updated values you want to change.
  -> Id -- ^ "id" -  Task ID
  -> VikunjaRequest TasksIdPositionPost MimeJSON ModelsTaskPosition MimeJSON
tasksIdPositionPost :: ModelsTaskPosition
-> Id
-> VikunjaRequest
     TasksIdPositionPost MimeJSON ModelsTaskPosition MimeJSON
tasksIdPositionPost ModelsTaskPosition
view (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksIdPositionPost MimeJSON ModelsTaskPosition 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
id,ByteString
"/position"]
    VikunjaRequest
  TasksIdPositionPost MimeJSON ModelsTaskPosition MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksIdPositionPost MimeJSON ModelsTaskPosition 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
  TasksIdPositionPost MimeJSON ModelsTaskPosition MimeJSON
-> ModelsTaskPosition
-> VikunjaRequest
     TasksIdPositionPost MimeJSON ModelsTaskPosition 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` ModelsTaskPosition
view

data TasksIdPositionPost 

-- | /Body Param/ "view" - The task position with updated values you want to change.
instance HasBodyParam TasksIdPositionPost ModelsTaskPosition 

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

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


-- *** tasksIdPost

-- | @POST \/tasks\/{id}@
-- 
-- Update a task
-- 
-- Updates a task. This includes marking it as done. Assignees you pass will be updated, see their individual endpoints for more details on how this is done. To update labels, see the description of the endpoint.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksIdPost
  :: (Consumes TasksIdPost MimeJSON, MimeRender MimeJSON ModelsTask)
  => ModelsTask -- ^ "task" -  The task object
  -> Id -- ^ "id" -  The Task ID
  -> VikunjaRequest TasksIdPost MimeJSON ModelsTask MimeJSON
tasksIdPost :: ModelsTask
-> Id -> VikunjaRequest TasksIdPost MimeJSON ModelsTask MimeJSON
tasksIdPost ModelsTask
task (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest TasksIdPost MimeJSON ModelsTask 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
id]
    VikunjaRequest TasksIdPost MimeJSON ModelsTask MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest TasksIdPost MimeJSON ModelsTask 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 TasksIdPost MimeJSON ModelsTask MimeJSON
-> ModelsTask
-> VikunjaRequest TasksIdPost MimeJSON ModelsTask 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` ModelsTask
task

data TasksIdPost 

-- | /Body Param/ "task" - The task object
instance HasBodyParam TasksIdPost ModelsTask 

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

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


-- *** tasksTaskIDCommentsCommentIDDelete

-- | @DELETE \/tasks\/{taskID}\/comments\/{commentID}@
-- 
-- Remove a task comment
-- 
-- Remove a task comment. The user doing this need to have at least write access to the task this comment belongs to.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDCommentsCommentIDDelete
  :: TaskId -- ^ "taskId" -  Task ID
  -> CommentId -- ^ "commentId" -  Comment ID
  -> VikunjaRequest TasksTaskIDCommentsCommentIDDelete MimeNoContent ModelsMessage MimeJSON
tasksTaskIDCommentsCommentIDDelete :: TaskId
-> CommentId
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
tasksTaskIDCommentsCommentIDDelete (TaskId Int
taskId) (CommentId Int
commentId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDDelete
     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
taskId,ByteString
"/comments/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
commentId]
    VikunjaRequest
  TasksTaskIDCommentsCommentIDDelete
  MimeNoContent
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDDelete
     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 TasksTaskIDCommentsCommentIDDelete  
-- | @application/json@
instance Produces TasksTaskIDCommentsCommentIDDelete MimeJSON


-- *** tasksTaskIDCommentsCommentIDGet

-- | @GET \/tasks\/{taskID}\/comments\/{commentID}@
-- 
-- Remove a task comment
-- 
-- Remove a task comment. The user doing this need to have at least read access to the task this comment belongs to.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDCommentsCommentIDGet
  :: TaskId -- ^ "taskId" -  Task ID
  -> CommentId -- ^ "commentId" -  Comment ID
  -> VikunjaRequest TasksTaskIDCommentsCommentIDGet MimeNoContent ModelsTaskComment MimeJSON
tasksTaskIDCommentsCommentIDGet :: TaskId
-> CommentId
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDGet
     MimeNoContent
     ModelsTaskComment
     MimeJSON
tasksTaskIDCommentsCommentIDGet (TaskId Int
taskId) (CommentId Int
commentId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDGet
     MimeNoContent
     ModelsTaskComment
     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
taskId,ByteString
"/comments/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
commentId]
    VikunjaRequest
  TasksTaskIDCommentsCommentIDGet
  MimeNoContent
  ModelsTaskComment
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDGet
     MimeNoContent
     ModelsTaskComment
     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 TasksTaskIDCommentsCommentIDGet  
-- | @application/json@
instance Produces TasksTaskIDCommentsCommentIDGet MimeJSON


-- *** tasksTaskIDCommentsCommentIDPost

-- | @POST \/tasks\/{taskID}\/comments\/{commentID}@
-- 
-- Update an existing task comment
-- 
-- Update an existing task comment. The user doing this need to have at least write access to the task this comment belongs to.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDCommentsCommentIDPost
  :: TaskId -- ^ "taskId" -  Task ID
  -> CommentId -- ^ "commentId" -  Comment ID
  -> VikunjaRequest TasksTaskIDCommentsCommentIDPost MimeNoContent ModelsTaskComment MimeJSON
tasksTaskIDCommentsCommentIDPost :: TaskId
-> CommentId
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDPost
     MimeNoContent
     ModelsTaskComment
     MimeJSON
tasksTaskIDCommentsCommentIDPost (TaskId Int
taskId) (CommentId Int
commentId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDPost
     MimeNoContent
     ModelsTaskComment
     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
"/comments/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
commentId]
    VikunjaRequest
  TasksTaskIDCommentsCommentIDPost
  MimeNoContent
  ModelsTaskComment
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDCommentsCommentIDPost
     MimeNoContent
     ModelsTaskComment
     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 TasksTaskIDCommentsCommentIDPost  
-- | @application/json@
instance Produces TasksTaskIDCommentsCommentIDPost MimeJSON


-- *** tasksTaskIDCommentsGet

-- | @GET \/tasks\/{taskID}\/comments@
-- 
-- Get all task comments
-- 
-- Get all task comments. The user doing this need to have at least read access to the task.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDCommentsGet
  :: TaskId -- ^ "taskId" -  Task ID
  -> VikunjaRequest TasksTaskIDCommentsGet MimeNoContent [ModelsTaskComment] MimeJSON
tasksTaskIDCommentsGet :: TaskId
-> VikunjaRequest
     TasksTaskIDCommentsGet MimeNoContent [ModelsTaskComment] MimeJSON
tasksTaskIDCommentsGet (TaskId Int
taskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDCommentsGet MimeNoContent [ModelsTaskComment] 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
taskId,ByteString
"/comments"]
    VikunjaRequest
  TasksTaskIDCommentsGet MimeNoContent [ModelsTaskComment] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDCommentsGet MimeNoContent [ModelsTaskComment] 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 TasksTaskIDCommentsGet  
-- | @application/json@
instance Produces TasksTaskIDCommentsGet MimeJSON


-- *** tasksTaskIDCommentsPut

-- | @PUT \/tasks\/{taskID}\/comments@
-- 
-- Create a new task comment
-- 
-- Create a new task comment. The user doing this need to have at least write access to the task this comment should belong to.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDCommentsPut
  :: (Consumes TasksTaskIDCommentsPut MimeJSON, MimeRender MimeJSON ModelsTaskComment)
  => ModelsTaskComment -- ^ "relation" -  The task comment object
  -> TaskId -- ^ "taskId" -  Task ID
  -> VikunjaRequest TasksTaskIDCommentsPut MimeJSON ModelsTaskComment MimeJSON
tasksTaskIDCommentsPut :: ModelsTaskComment
-> TaskId
-> VikunjaRequest
     TasksTaskIDCommentsPut MimeJSON ModelsTaskComment MimeJSON
tasksTaskIDCommentsPut ModelsTaskComment
relation (TaskId Int
taskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDCommentsPut MimeJSON ModelsTaskComment 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
taskId,ByteString
"/comments"]
    VikunjaRequest
  TasksTaskIDCommentsPut MimeJSON ModelsTaskComment MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDCommentsPut MimeJSON ModelsTaskComment 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
  TasksTaskIDCommentsPut MimeJSON ModelsTaskComment MimeJSON
-> ModelsTaskComment
-> VikunjaRequest
     TasksTaskIDCommentsPut MimeJSON ModelsTaskComment 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` ModelsTaskComment
relation

data TasksTaskIDCommentsPut 

-- | /Body Param/ "relation" - The task comment object
instance HasBodyParam TasksTaskIDCommentsPut ModelsTaskComment 

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

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


-- *** tasksTaskIDRelationsPut

-- | @PUT \/tasks\/{taskID}\/relations@
-- 
-- Create a new relation between two tasks
-- 
-- Creates a new relation between two tasks. The user needs to have update rights on the base task and at least read rights on the other task. Both tasks do not need to be on the same project. Take a look at the docs for available task relation kinds.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDRelationsPut
  :: (Consumes TasksTaskIDRelationsPut MimeJSON, MimeRender MimeJSON ModelsTaskRelation)
  => ModelsTaskRelation -- ^ "relation" -  The relation object
  -> TaskId -- ^ "taskId" -  Task ID
  -> VikunjaRequest TasksTaskIDRelationsPut MimeJSON ModelsTaskRelation MimeJSON
tasksTaskIDRelationsPut :: ModelsTaskRelation
-> TaskId
-> VikunjaRequest
     TasksTaskIDRelationsPut MimeJSON ModelsTaskRelation MimeJSON
tasksTaskIDRelationsPut ModelsTaskRelation
relation (TaskId Int
taskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDRelationsPut MimeJSON ModelsTaskRelation 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
taskId,ByteString
"/relations"]
    VikunjaRequest
  TasksTaskIDRelationsPut MimeJSON ModelsTaskRelation MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDRelationsPut MimeJSON ModelsTaskRelation 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
  TasksTaskIDRelationsPut MimeJSON ModelsTaskRelation MimeJSON
-> ModelsTaskRelation
-> VikunjaRequest
     TasksTaskIDRelationsPut MimeJSON ModelsTaskRelation 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` ModelsTaskRelation
relation

data TasksTaskIDRelationsPut 

-- | /Body Param/ "relation" - The relation object
instance HasBodyParam TasksTaskIDRelationsPut ModelsTaskRelation 

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

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


-- *** tasksTaskIDRelationsRelationKindOtherTaskIDDelete

-- | @DELETE \/tasks\/{taskID}\/relations\/{relationKind}\/{otherTaskID}@
-- 
-- Remove a task relation
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDRelationsRelationKindOtherTaskIDDelete
  :: (Consumes TasksTaskIDRelationsRelationKindOtherTaskIDDelete MimeJSON, MimeRender MimeJSON ModelsTaskRelation)
  => ModelsTaskRelation -- ^ "relation" -  The relation object
  -> TaskId -- ^ "taskId" -  Task ID
  -> RelationKind -- ^ "relationKind" -  The kind of the relation. See the TaskRelation type for more info.
  -> OtherTaskId -- ^ "otherTaskId" -  The id of the other task.
  -> VikunjaRequest TasksTaskIDRelationsRelationKindOtherTaskIDDelete MimeJSON ModelsMessage MimeJSON
tasksTaskIDRelationsRelationKindOtherTaskIDDelete :: ModelsTaskRelation
-> TaskId
-> RelationKind
-> OtherTaskId
-> VikunjaRequest
     TasksTaskIDRelationsRelationKindOtherTaskIDDelete
     MimeJSON
     ModelsMessage
     MimeJSON
tasksTaskIDRelationsRelationKindOtherTaskIDDelete ModelsTaskRelation
relation (TaskId Int
taskId) (RelationKind Text
relationKind) (OtherTaskId Int
otherTaskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDRelationsRelationKindOtherTaskIDDelete
     MimeJSON
     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
taskId,ByteString
"/relations/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
relationKind,ByteString
"/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
otherTaskId]
    VikunjaRequest
  TasksTaskIDRelationsRelationKindOtherTaskIDDelete
  MimeJSON
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDRelationsRelationKindOtherTaskIDDelete
     MimeJSON
     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)
    VikunjaRequest
  TasksTaskIDRelationsRelationKindOtherTaskIDDelete
  MimeJSON
  ModelsMessage
  MimeJSON
-> ModelsTaskRelation
-> VikunjaRequest
     TasksTaskIDRelationsRelationKindOtherTaskIDDelete
     MimeJSON
     ModelsMessage
     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` ModelsTaskRelation
relation

data TasksTaskIDRelationsRelationKindOtherTaskIDDelete 

-- | /Body Param/ "relation" - The relation object
instance HasBodyParam TasksTaskIDRelationsRelationKindOtherTaskIDDelete ModelsTaskRelation 

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

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