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

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


-- ** Assignees

-- *** tasksTaskIDAssigneesBulkPost

-- | @POST \/tasks\/{taskID}\/assignees\/bulk@
-- 
-- Add multiple new assignees to a task
-- 
-- Adds multiple new assignees to a task. The assignee needs to have access to the project, the doer must be able to edit this task. Every user not in the project will be unassigned from the task, pass an empty array to unassign everyone.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDAssigneesBulkPost
  :: (Consumes TasksTaskIDAssigneesBulkPost MimeJSON, MimeRender MimeJSON ModelsBulkAssignees)
  => ModelsBulkAssignees -- ^ "assignee" -  The array of assignees
  -> TaskId -- ^ "taskId" -  Task ID
  -> VikunjaRequest TasksTaskIDAssigneesBulkPost MimeJSON ModelsTaskAssginee MimeJSON
tasksTaskIDAssigneesBulkPost :: ModelsBulkAssignees
-> TaskId
-> VikunjaRequest
     TasksTaskIDAssigneesBulkPost MimeJSON ModelsTaskAssginee MimeJSON
tasksTaskIDAssigneesBulkPost ModelsBulkAssignees
assignee (TaskId Int
taskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDAssigneesBulkPost MimeJSON ModelsTaskAssginee 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
"/assignees/bulk"]
    VikunjaRequest
  TasksTaskIDAssigneesBulkPost MimeJSON ModelsTaskAssginee MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDAssigneesBulkPost MimeJSON ModelsTaskAssginee 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
  TasksTaskIDAssigneesBulkPost MimeJSON ModelsTaskAssginee MimeJSON
-> ModelsBulkAssignees
-> VikunjaRequest
     TasksTaskIDAssigneesBulkPost MimeJSON ModelsTaskAssginee 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` ModelsBulkAssignees
assignee

data TasksTaskIDAssigneesBulkPost 

-- | /Body Param/ "assignee" - The array of assignees
instance HasBodyParam TasksTaskIDAssigneesBulkPost ModelsBulkAssignees 

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

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


-- *** tasksTaskIDAssigneesGet

-- | @GET \/tasks\/{taskID}\/assignees@
-- 
-- Get all assignees for a task
-- 
-- Returns an array with all assignees for this task.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDAssigneesGet
  :: TaskId -- ^ "taskId" -  Task ID
  -> VikunjaRequest TasksTaskIDAssigneesGet MimeNoContent [UserUser] MimeJSON
tasksTaskIDAssigneesGet :: TaskId
-> VikunjaRequest
     TasksTaskIDAssigneesGet MimeNoContent [UserUser] MimeJSON
tasksTaskIDAssigneesGet (TaskId Int
taskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDAssigneesGet MimeNoContent [UserUser] 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
"/assignees"]
    VikunjaRequest
  TasksTaskIDAssigneesGet MimeNoContent [UserUser] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDAssigneesGet MimeNoContent [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 TasksTaskIDAssigneesGet  

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


-- *** tasksTaskIDAssigneesPut

-- | @PUT \/tasks\/{taskID}\/assignees@
-- 
-- Add a new assignee to a task
-- 
-- Adds a new assignee to a task. The assignee needs to have access to the project, the doer must be able to edit this task.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDAssigneesPut
  :: (Consumes TasksTaskIDAssigneesPut MimeJSON, MimeRender MimeJSON ModelsTaskAssginee)
  => ModelsTaskAssginee -- ^ "assignee" -  The assingee object
  -> TaskId -- ^ "taskId" -  Task ID
  -> VikunjaRequest TasksTaskIDAssigneesPut MimeJSON ModelsTaskAssginee MimeJSON
tasksTaskIDAssigneesPut :: ModelsTaskAssginee
-> TaskId
-> VikunjaRequest
     TasksTaskIDAssigneesPut MimeJSON ModelsTaskAssginee MimeJSON
tasksTaskIDAssigneesPut ModelsTaskAssginee
assignee (TaskId Int
taskId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDAssigneesPut MimeJSON ModelsTaskAssginee 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
"/assignees"]
    VikunjaRequest
  TasksTaskIDAssigneesPut MimeJSON ModelsTaskAssginee MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDAssigneesPut MimeJSON ModelsTaskAssginee 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
  TasksTaskIDAssigneesPut MimeJSON ModelsTaskAssginee MimeJSON
-> ModelsTaskAssginee
-> VikunjaRequest
     TasksTaskIDAssigneesPut MimeJSON ModelsTaskAssginee 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` ModelsTaskAssginee
assignee

data TasksTaskIDAssigneesPut 

-- | /Body Param/ "assignee" - The assingee object
instance HasBodyParam TasksTaskIDAssigneesPut ModelsTaskAssginee 

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

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


-- *** tasksTaskIDAssigneesUserIDDelete

-- | @DELETE \/tasks\/{taskID}\/assignees\/{userID}@
-- 
-- Delete an assignee
-- 
-- Un-assign a user from a task.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
tasksTaskIDAssigneesUserIDDelete
  :: TaskId -- ^ "taskId" -  Task ID
  -> UserId -- ^ "userId" -  Assignee user ID
  -> VikunjaRequest TasksTaskIDAssigneesUserIDDelete MimeNoContent ModelsMessage MimeJSON
tasksTaskIDAssigneesUserIDDelete :: TaskId
-> UserId
-> VikunjaRequest
     TasksTaskIDAssigneesUserIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
tasksTaskIDAssigneesUserIDDelete (TaskId Int
taskId) (UserId Int
userId) =
  Method
-> [ByteString]
-> VikunjaRequest
     TasksTaskIDAssigneesUserIDDelete
     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
"/assignees/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
userId]
    VikunjaRequest
  TasksTaskIDAssigneesUserIDDelete
  MimeNoContent
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     TasksTaskIDAssigneesUserIDDelete
     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 TasksTaskIDAssigneesUserIDDelete  
-- | @application/json@
instance Produces TasksTaskIDAssigneesUserIDDelete MimeJSON