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

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


-- ** Sharing

-- *** notificationsPost

-- | @POST \/notifications@
-- 
-- Mark all notifications of a user as read
-- 
notificationsPost
  :: VikunjaRequest NotificationsPost MimeNoContent ModelsMessage MimeJSON
notificationsPost :: VikunjaRequest
  NotificationsPost MimeNoContent ModelsMessage MimeJSON
notificationsPost =
  Method
-> [ByteString]
-> VikunjaRequest
     NotificationsPost MimeNoContent ModelsMessage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/notifications"]

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


-- *** projectsIdTeamsGet

-- | @GET \/projects\/{id}\/teams@
-- 
-- Get teams on a project
-- 
-- Returns a project with all teams which have access on a given project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdTeamsGet
  :: Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdTeamsGet MimeNoContent [ModelsTeamWithRight] MimeJSON
projectsIdTeamsGet :: Id
-> VikunjaRequest
     ProjectsIdTeamsGet MimeNoContent [ModelsTeamWithRight] MimeJSON
projectsIdTeamsGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdTeamsGet MimeNoContent [ModelsTeamWithRight] 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
"/teams"]
    VikunjaRequest
  ProjectsIdTeamsGet MimeNoContent [ModelsTeamWithRight] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdTeamsGet MimeNoContent [ModelsTeamWithRight] 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 ProjectsIdTeamsGet  

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


-- *** projectsIdTeamsPut

-- | @PUT \/projects\/{id}\/teams@
-- 
-- Add a team to a project
-- 
-- Gives a team access to a project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdTeamsPut
  :: (Consumes ProjectsIdTeamsPut MimeJSON, MimeRender MimeJSON ModelsTeamProject)
  => ModelsTeamProject -- ^ "project" -  The team you want to add to the project.
  -> Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdTeamsPut MimeJSON ModelsTeamProject MimeJSON
projectsIdTeamsPut :: ModelsTeamProject
-> Id
-> VikunjaRequest
     ProjectsIdTeamsPut MimeJSON ModelsTeamProject MimeJSON
projectsIdTeamsPut ModelsTeamProject
project (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdTeamsPut MimeJSON ModelsTeamProject 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
"/teams"]
    VikunjaRequest
  ProjectsIdTeamsPut MimeJSON ModelsTeamProject MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdTeamsPut MimeJSON ModelsTeamProject 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
  ProjectsIdTeamsPut MimeJSON ModelsTeamProject MimeJSON
-> ModelsTeamProject
-> VikunjaRequest
     ProjectsIdTeamsPut MimeJSON ModelsTeamProject 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` ModelsTeamProject
project

data ProjectsIdTeamsPut 

-- | /Body Param/ "project" - The team you want to add to the project.
instance HasBodyParam ProjectsIdTeamsPut ModelsTeamProject 

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

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


-- *** projectsIdUsersGet

-- | @GET \/projects\/{id}\/users@
-- 
-- Get users on a project
-- 
-- Returns a project with all users which have access on a given project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdUsersGet
  :: Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdUsersGet MimeNoContent [ModelsUserWithRight] MimeJSON
projectsIdUsersGet :: Id
-> VikunjaRequest
     ProjectsIdUsersGet MimeNoContent [ModelsUserWithRight] MimeJSON
projectsIdUsersGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdUsersGet MimeNoContent [ModelsUserWithRight] 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
"/users"]
    VikunjaRequest
  ProjectsIdUsersGet MimeNoContent [ModelsUserWithRight] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdUsersGet MimeNoContent [ModelsUserWithRight] 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 ProjectsIdUsersGet  

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


-- *** projectsIdUsersPut

-- | @PUT \/projects\/{id}\/users@
-- 
-- Add a user to a project
-- 
-- Gives a user access to a project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdUsersPut
  :: (Consumes ProjectsIdUsersPut MimeJSON, MimeRender MimeJSON ModelsProjectUser)
  => ModelsProjectUser -- ^ "project" -  The user you want to add to the project.
  -> Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdUsersPut MimeJSON ModelsProjectUser MimeJSON
projectsIdUsersPut :: ModelsProjectUser
-> Id
-> VikunjaRequest
     ProjectsIdUsersPut MimeJSON ModelsProjectUser MimeJSON
projectsIdUsersPut ModelsProjectUser
project (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdUsersPut MimeJSON ModelsProjectUser 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
"/users"]
    VikunjaRequest
  ProjectsIdUsersPut MimeJSON ModelsProjectUser MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdUsersPut MimeJSON ModelsProjectUser 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
  ProjectsIdUsersPut MimeJSON ModelsProjectUser MimeJSON
-> ModelsProjectUser
-> VikunjaRequest
     ProjectsIdUsersPut MimeJSON ModelsProjectUser 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` ModelsProjectUser
project

data ProjectsIdUsersPut 

-- | /Body Param/ "project" - The user you want to add to the project.
instance HasBodyParam ProjectsIdUsersPut ModelsProjectUser 

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

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


-- *** projectsProjectIDTeamsTeamIDDelete

-- | @DELETE \/projects\/{projectID}\/teams\/{teamID}@
-- 
-- Delete a team from a project
-- 
-- Delets a team from a project. The team won't have access to the project anymore.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectIDTeamsTeamIDDelete
  :: ProjectId -- ^ "projectId" -  Project ID
  -> TeamId -- ^ "teamId" -  Team ID
  -> VikunjaRequest ProjectsProjectIDTeamsTeamIDDelete MimeNoContent ModelsMessage MimeJSON
projectsProjectIDTeamsTeamIDDelete :: ProjectId
-> TeamId
-> VikunjaRequest
     ProjectsProjectIDTeamsTeamIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
projectsProjectIDTeamsTeamIDDelete (ProjectId Int
projectId) (TeamId Int
teamId) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectIDTeamsTeamIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/projects/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
projectId,ByteString
"/teams/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
teamId]
    VikunjaRequest
  ProjectsProjectIDTeamsTeamIDDelete
  MimeNoContent
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectIDTeamsTeamIDDelete
     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 ProjectsProjectIDTeamsTeamIDDelete  
-- | @application/json@
instance Produces ProjectsProjectIDTeamsTeamIDDelete MimeJSON


-- *** projectsProjectIDTeamsTeamIDPost

-- | @POST \/projects\/{projectID}\/teams\/{teamID}@
-- 
-- Update a team <-> project relation
-- 
-- Update a team <-> project relation. Mostly used to update the right that team has.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectIDTeamsTeamIDPost
  :: (Consumes ProjectsProjectIDTeamsTeamIDPost MimeJSON, MimeRender MimeJSON ModelsTeamProject)
  => ModelsTeamProject -- ^ "project" -  The team you want to update.
  -> ProjectId -- ^ "projectId" -  Project ID
  -> TeamId -- ^ "teamId" -  Team ID
  -> VikunjaRequest ProjectsProjectIDTeamsTeamIDPost MimeJSON ModelsTeamProject MimeJSON
projectsProjectIDTeamsTeamIDPost :: ModelsTeamProject
-> ProjectId
-> TeamId
-> VikunjaRequest
     ProjectsProjectIDTeamsTeamIDPost
     MimeJSON
     ModelsTeamProject
     MimeJSON
projectsProjectIDTeamsTeamIDPost ModelsTeamProject
project (ProjectId Int
projectId) (TeamId Int
teamId) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectIDTeamsTeamIDPost
     MimeJSON
     ModelsTeamProject
     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
projectId,ByteString
"/teams/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
teamId]
    VikunjaRequest
  ProjectsProjectIDTeamsTeamIDPost
  MimeJSON
  ModelsTeamProject
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectIDTeamsTeamIDPost
     MimeJSON
     ModelsTeamProject
     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
  ProjectsProjectIDTeamsTeamIDPost
  MimeJSON
  ModelsTeamProject
  MimeJSON
-> ModelsTeamProject
-> VikunjaRequest
     ProjectsProjectIDTeamsTeamIDPost
     MimeJSON
     ModelsTeamProject
     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` ModelsTeamProject
project

data ProjectsProjectIDTeamsTeamIDPost 

-- | /Body Param/ "project" - The team you want to update.
instance HasBodyParam ProjectsProjectIDTeamsTeamIDPost ModelsTeamProject 

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

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


-- *** projectsProjectIDUsersUserIDDelete

-- | @DELETE \/projects\/{projectID}\/users\/{userID}@
-- 
-- Delete a user from a project
-- 
-- Delets a user from a project. The user won't have access to the project anymore.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectIDUsersUserIDDelete
  :: ProjectId -- ^ "projectId" -  Project ID
  -> UserId -- ^ "userId" -  User ID
  -> VikunjaRequest ProjectsProjectIDUsersUserIDDelete MimeNoContent ModelsMessage MimeJSON
projectsProjectIDUsersUserIDDelete :: ProjectId
-> UserId
-> VikunjaRequest
     ProjectsProjectIDUsersUserIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
projectsProjectIDUsersUserIDDelete (ProjectId Int
projectId) (UserId Int
userId) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectIDUsersUserIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/projects/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
projectId,ByteString
"/users/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
userId]
    VikunjaRequest
  ProjectsProjectIDUsersUserIDDelete
  MimeNoContent
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectIDUsersUserIDDelete
     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 ProjectsProjectIDUsersUserIDDelete  
-- | @application/json@
instance Produces ProjectsProjectIDUsersUserIDDelete MimeJSON


-- *** projectsProjectIDUsersUserIDPost

-- | @POST \/projects\/{projectID}\/users\/{userID}@
-- 
-- Update a user <-> project relation
-- 
-- Update a user <-> project relation. Mostly used to update the right that user has.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectIDUsersUserIDPost
  :: (Consumes ProjectsProjectIDUsersUserIDPost MimeJSON, MimeRender MimeJSON ModelsProjectUser)
  => ModelsProjectUser -- ^ "project" -  The user you want to update.
  -> ProjectId -- ^ "projectId" -  Project ID
  -> UserId -- ^ "userId" -  User ID
  -> VikunjaRequest ProjectsProjectIDUsersUserIDPost MimeJSON ModelsProjectUser MimeJSON
projectsProjectIDUsersUserIDPost :: ModelsProjectUser
-> ProjectId
-> UserId
-> VikunjaRequest
     ProjectsProjectIDUsersUserIDPost
     MimeJSON
     ModelsProjectUser
     MimeJSON
projectsProjectIDUsersUserIDPost ModelsProjectUser
project (ProjectId Int
projectId) (UserId Int
userId) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectIDUsersUserIDPost
     MimeJSON
     ModelsProjectUser
     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
projectId,ByteString
"/users/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
userId]
    VikunjaRequest
  ProjectsProjectIDUsersUserIDPost
  MimeJSON
  ModelsProjectUser
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectIDUsersUserIDPost
     MimeJSON
     ModelsProjectUser
     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
  ProjectsProjectIDUsersUserIDPost
  MimeJSON
  ModelsProjectUser
  MimeJSON
-> ModelsProjectUser
-> VikunjaRequest
     ProjectsProjectIDUsersUserIDPost
     MimeJSON
     ModelsProjectUser
     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` ModelsProjectUser
project

data ProjectsProjectIDUsersUserIDPost 

-- | /Body Param/ "project" - The user you want to update.
instance HasBodyParam ProjectsProjectIDUsersUserIDPost ModelsProjectUser 

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

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


-- *** projectsProjectSharesGet

-- | @GET \/projects\/{project}\/shares@
-- 
-- Get all link shares for a project
-- 
-- Returns all link shares which exist for a given project
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectSharesGet
  :: Project -- ^ "project" -  Project ID
  -> VikunjaRequest ProjectsProjectSharesGet MimeNoContent [ModelsLinkSharing] MimeJSON
projectsProjectSharesGet :: Project
-> VikunjaRequest
     ProjectsProjectSharesGet MimeNoContent [ModelsLinkSharing] MimeJSON
projectsProjectSharesGet (Project Int
project) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectSharesGet MimeNoContent [ModelsLinkSharing] 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
project,ByteString
"/shares"]
    VikunjaRequest
  ProjectsProjectSharesGet MimeNoContent [ModelsLinkSharing] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectSharesGet MimeNoContent [ModelsLinkSharing] 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 ProjectsProjectSharesGet  

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


-- *** projectsProjectSharesPut

-- | @PUT \/projects\/{project}\/shares@
-- 
-- Share a project via link
-- 
-- Share a project via link. The user needs to have write-access to the project to be able do this.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectSharesPut
  :: (Consumes ProjectsProjectSharesPut MimeJSON, MimeRender MimeJSON ModelsLinkSharing)
  => ModelsLinkSharing -- ^ "label" -  The new link share object
  -> Project -- ^ "project" -  Project ID
  -> VikunjaRequest ProjectsProjectSharesPut MimeJSON ModelsLinkSharing MimeJSON
projectsProjectSharesPut :: ModelsLinkSharing
-> Project
-> VikunjaRequest
     ProjectsProjectSharesPut MimeJSON ModelsLinkSharing MimeJSON
projectsProjectSharesPut ModelsLinkSharing
label (Project Int
project) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectSharesPut MimeJSON ModelsLinkSharing 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
project,ByteString
"/shares"]
    VikunjaRequest
  ProjectsProjectSharesPut MimeJSON ModelsLinkSharing MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectSharesPut MimeJSON ModelsLinkSharing 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
  ProjectsProjectSharesPut MimeJSON ModelsLinkSharing MimeJSON
-> ModelsLinkSharing
-> VikunjaRequest
     ProjectsProjectSharesPut MimeJSON ModelsLinkSharing 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` ModelsLinkSharing
label

data ProjectsProjectSharesPut 

-- | /Body Param/ "label" - The new link share object
instance HasBodyParam ProjectsProjectSharesPut ModelsLinkSharing 

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

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


-- *** projectsProjectSharesShareDelete

-- | @DELETE \/projects\/{project}\/shares\/{share}@
-- 
-- Remove a link share
-- 
-- Remove a link share. The user needs to have write-access to the project to be able do this.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectSharesShareDelete
  :: Project -- ^ "project" -  Project ID
  -> Share -- ^ "share" -  Share Link ID
  -> VikunjaRequest ProjectsProjectSharesShareDelete MimeNoContent ModelsMessage MimeJSON
projectsProjectSharesShareDelete :: Project
-> Share
-> VikunjaRequest
     ProjectsProjectSharesShareDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
projectsProjectSharesShareDelete (Project Int
project) (Share Int
share) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectSharesShareDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/projects/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
project,ByteString
"/shares/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
share]
    VikunjaRequest
  ProjectsProjectSharesShareDelete
  MimeNoContent
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectSharesShareDelete
     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 ProjectsProjectSharesShareDelete  
-- | @application/json@
instance Produces ProjectsProjectSharesShareDelete MimeJSON


-- *** projectsProjectSharesShareGet

-- | @GET \/projects\/{project}\/shares\/{share}@
-- 
-- Get one link shares for a project
-- 
-- Returns one link share by its ID.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectSharesShareGet
  :: Project -- ^ "project" -  Project ID
  -> Share -- ^ "share" -  Share ID
  -> VikunjaRequest ProjectsProjectSharesShareGet MimeNoContent ModelsLinkSharing MimeJSON
projectsProjectSharesShareGet :: Project
-> Share
-> VikunjaRequest
     ProjectsProjectSharesShareGet
     MimeNoContent
     ModelsLinkSharing
     MimeJSON
projectsProjectSharesShareGet (Project Int
project) (Share Int
share) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectSharesShareGet
     MimeNoContent
     ModelsLinkSharing
     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
project,ByteString
"/shares/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
share]
    VikunjaRequest
  ProjectsProjectSharesShareGet
  MimeNoContent
  ModelsLinkSharing
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectSharesShareGet
     MimeNoContent
     ModelsLinkSharing
     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 ProjectsProjectSharesShareGet  
-- | @application/json@
instance Produces ProjectsProjectSharesShareGet MimeJSON


-- *** sharesShareAuthPost

-- | @POST \/shares\/{share}\/auth@
-- 
-- Get an auth token for a share
-- 
-- Get a jwt auth token for a shared project from a share hash.
-- 
sharesShareAuthPost
  :: (Consumes SharesShareAuthPost MimeJSON, MimeRender MimeJSON V1LinkShareAuth)
  => V1LinkShareAuth -- ^ "password" -  The password for link shares which require one.
  -> ShareText -- ^ "share" -  The share hash
  -> VikunjaRequest SharesShareAuthPost MimeJSON AuthToken MimeJSON
sharesShareAuthPost :: V1LinkShareAuth
-> ShareText
-> VikunjaRequest SharesShareAuthPost MimeJSON AuthToken MimeJSON
sharesShareAuthPost V1LinkShareAuth
password (ShareText Text
share) =
  Method
-> [ByteString]
-> VikunjaRequest SharesShareAuthPost MimeJSON AuthToken MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/shares/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
share,ByteString
"/auth"]
    VikunjaRequest SharesShareAuthPost MimeJSON AuthToken MimeJSON
-> V1LinkShareAuth
-> VikunjaRequest SharesShareAuthPost MimeJSON AuthToken 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` V1LinkShareAuth
password

data SharesShareAuthPost 

-- | /Body Param/ "password" - The password for link shares which require one.
instance HasBodyParam SharesShareAuthPost V1LinkShareAuth 

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

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