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

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


-- ** Project

-- *** backgroundsUnsplashImageImageGet

-- | @GET \/backgrounds\/unsplash\/image\/{image}@
-- 
-- Get an unsplash image
-- 
-- Get an unsplash image. **Returns json on error.**
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
backgroundsUnsplashImageImageGet
  :: Image -- ^ "image" -  Unsplash Image ID
  -> VikunjaRequest BackgroundsUnsplashImageImageGet MimeNoContent FilePath MimeOctetStream
backgroundsUnsplashImageImageGet :: Image
-> VikunjaRequest
     BackgroundsUnsplashImageImageGet
     MimeNoContent
     FilePath
     MimeOctetStream
backgroundsUnsplashImageImageGet (Image Int
image) =
  Method
-> [ByteString]
-> VikunjaRequest
     BackgroundsUnsplashImageImageGet
     MimeNoContent
     FilePath
     MimeOctetStream
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/backgrounds/unsplash/image/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
image]
    VikunjaRequest
  BackgroundsUnsplashImageImageGet
  MimeNoContent
  FilePath
  MimeOctetStream
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     BackgroundsUnsplashImageImageGet
     MimeNoContent
     FilePath
     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 BackgroundsUnsplashImageImageGet  
-- | @application/octet-stream@
instance Produces BackgroundsUnsplashImageImageGet MimeOctetStream


-- *** backgroundsUnsplashImageImageThumbGet

-- | @GET \/backgrounds\/unsplash\/image\/{image}\/thumb@
-- 
-- Get an unsplash thumbnail image
-- 
-- Get an unsplash thumbnail image. The thumbnail is cropped to a max width of 200px. **Returns json on error.**
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
backgroundsUnsplashImageImageThumbGet
  :: Image -- ^ "image" -  Unsplash Image ID
  -> VikunjaRequest BackgroundsUnsplashImageImageThumbGet MimeNoContent FilePath MimeOctetStream
backgroundsUnsplashImageImageThumbGet :: Image
-> VikunjaRequest
     BackgroundsUnsplashImageImageThumbGet
     MimeNoContent
     FilePath
     MimeOctetStream
backgroundsUnsplashImageImageThumbGet (Image Int
image) =
  Method
-> [ByteString]
-> VikunjaRequest
     BackgroundsUnsplashImageImageThumbGet
     MimeNoContent
     FilePath
     MimeOctetStream
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/backgrounds/unsplash/image/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
image,ByteString
"/thumb"]
    VikunjaRequest
  BackgroundsUnsplashImageImageThumbGet
  MimeNoContent
  FilePath
  MimeOctetStream
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     BackgroundsUnsplashImageImageThumbGet
     MimeNoContent
     FilePath
     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 BackgroundsUnsplashImageImageThumbGet  
-- | @application/octet-stream@
instance Produces BackgroundsUnsplashImageImageThumbGet MimeOctetStream


-- *** backgroundsUnsplashSearchGet

-- | @GET \/backgrounds\/unsplash\/search@
-- 
-- Search for a background from unsplash
-- 
-- Search for a project background from unsplash
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
backgroundsUnsplashSearchGet
  :: VikunjaRequest BackgroundsUnsplashSearchGet MimeNoContent [BackgroundImage] MimeJSON
backgroundsUnsplashSearchGet :: VikunjaRequest
  BackgroundsUnsplashSearchGet
  MimeNoContent
  [BackgroundImage]
  MimeJSON
backgroundsUnsplashSearchGet =
  Method
-> [ByteString]
-> VikunjaRequest
     BackgroundsUnsplashSearchGet
     MimeNoContent
     [BackgroundImage]
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/backgrounds/unsplash/search"]
    VikunjaRequest
  BackgroundsUnsplashSearchGet
  MimeNoContent
  [BackgroundImage]
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     BackgroundsUnsplashSearchGet
     MimeNoContent
     [BackgroundImage]
     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 BackgroundsUnsplashSearchGet  

-- | /Optional Param/ "s" - Search backgrounds from unsplash with this search term.
instance HasOptionalParam BackgroundsUnsplashSearchGet S where
  applyOptionalParam :: VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
-> S
-> VikunjaRequest
     BackgroundsUnsplashSearchGet contentType res accept
applyOptionalParam VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
req (S Text
xs) =
    VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
req VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     BackgroundsUnsplashSearchGet 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/ "p" - The page number. Used for pagination. If not provided, the first page of results is returned.
instance HasOptionalParam BackgroundsUnsplashSearchGet P where
  applyOptionalParam :: VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
-> P
-> VikunjaRequest
     BackgroundsUnsplashSearchGet contentType res accept
applyOptionalParam VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
req (P Int
xs) =
    VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
req VikunjaRequest BackgroundsUnsplashSearchGet contentType res accept
-> [QueryItem]
-> VikunjaRequest
     BackgroundsUnsplashSearchGet 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
"p", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
-- | @application/json@
instance Produces BackgroundsUnsplashSearchGet MimeJSON


-- *** projectsGet

-- | @GET \/projects@
-- 
-- Get all projects a user has access to
-- 
-- Returns all projects a user has access to.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsGet
  :: VikunjaRequest ProjectsGet MimeNoContent [ModelsProject] MimeJSON
projectsGet :: VikunjaRequest ProjectsGet MimeNoContent [ModelsProject] MimeJSON
projectsGet =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsGet MimeNoContent [ModelsProject] MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/projects"]
    VikunjaRequest ProjectsGet MimeNoContent [ModelsProject] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsGet MimeNoContent [ModelsProject] 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 ProjectsGet  

-- | /Optional Param/ "page" - The page number. Used for pagination. If not provided, the first page of results is returned.
instance HasOptionalParam ProjectsGet Page where
  applyOptionalParam :: VikunjaRequest ProjectsGet contentType res accept
-> Page -> VikunjaRequest ProjectsGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsGet contentType res accept
req (Page Int
xs) =
    VikunjaRequest ProjectsGet contentType res accept
req VikunjaRequest ProjectsGet contentType res accept
-> [QueryItem] -> VikunjaRequest ProjectsGet 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 ProjectsGet PerPage where
  applyOptionalParam :: VikunjaRequest ProjectsGet contentType res accept
-> PerPage -> VikunjaRequest ProjectsGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsGet contentType res accept
req (PerPage Int
xs) =
    VikunjaRequest ProjectsGet contentType res accept
req VikunjaRequest ProjectsGet contentType res accept
-> [QueryItem] -> VikunjaRequest ProjectsGet 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 projects by title.
instance HasOptionalParam ProjectsGet S where
  applyOptionalParam :: VikunjaRequest ProjectsGet contentType res accept
-> S -> VikunjaRequest ProjectsGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsGet contentType res accept
req (S Text
xs) =
    VikunjaRequest ProjectsGet contentType res accept
req VikunjaRequest ProjectsGet contentType res accept
-> [QueryItem] -> VikunjaRequest ProjectsGet 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/ "is_archived" - If true, also returns all archived projects.
instance HasOptionalParam ProjectsGet IsArchived where
  applyOptionalParam :: VikunjaRequest ProjectsGet contentType res accept
-> IsArchived -> VikunjaRequest ProjectsGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsGet contentType res accept
req (IsArchived Bool
xs) =
    VikunjaRequest ProjectsGet contentType res accept
req VikunjaRequest ProjectsGet contentType res accept
-> [QueryItem] -> VikunjaRequest ProjectsGet contentType res accept
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> [QueryItem] -> VikunjaRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"is_archived", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
-- | @application/json@
instance Produces ProjectsGet MimeJSON


-- *** projectsIdBackgroundDelete

-- | @DELETE \/projects\/{id}\/background@
-- 
-- Remove a project background
-- 
-- Removes a previously set project background, regardless of the project provider used to set the background. It does not throw an error if the project does not have a background.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdBackgroundDelete
  :: Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdBackgroundDelete MimeNoContent ModelsProject MimeJSON
projectsIdBackgroundDelete :: Id
-> VikunjaRequest
     ProjectsIdBackgroundDelete MimeNoContent ModelsProject MimeJSON
projectsIdBackgroundDelete (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdBackgroundDelete MimeNoContent ModelsProject 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
id,ByteString
"/background"]
    VikunjaRequest
  ProjectsIdBackgroundDelete MimeNoContent ModelsProject MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdBackgroundDelete MimeNoContent ModelsProject 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 ProjectsIdBackgroundDelete  
-- | @application/json@
instance Produces ProjectsIdBackgroundDelete MimeJSON


-- *** projectsIdBackgroundGet

-- | @GET \/projects\/{id}\/background@
-- 
-- Get the project background
-- 
-- Get the project background of a specific project. **Returns json on error.**
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdBackgroundGet
  :: Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdBackgroundGet MimeNoContent FilePath MimeOctetStream
projectsIdBackgroundGet :: Id
-> VikunjaRequest
     ProjectsIdBackgroundGet MimeNoContent FilePath MimeOctetStream
projectsIdBackgroundGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdBackgroundGet MimeNoContent FilePath MimeOctetStream
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
"/background"]
    VikunjaRequest
  ProjectsIdBackgroundGet MimeNoContent FilePath MimeOctetStream
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdBackgroundGet MimeNoContent FilePath 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 ProjectsIdBackgroundGet  
-- | @application/octet-stream@
instance Produces ProjectsIdBackgroundGet MimeOctetStream


-- *** projectsIdBackgroundsUnsplashPost

-- | @POST \/projects\/{id}\/backgrounds\/unsplash@
-- 
-- Set an unsplash photo as project background
-- 
-- Sets a photo from unsplash as project background.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdBackgroundsUnsplashPost
  :: (Consumes ProjectsIdBackgroundsUnsplashPost MimeJSON, MimeRender MimeJSON BackgroundImage)
  => BackgroundImage -- ^ "project" -  The image you want to set as background
  -> Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdBackgroundsUnsplashPost MimeJSON ModelsProject MimeJSON
projectsIdBackgroundsUnsplashPost :: BackgroundImage
-> Id
-> VikunjaRequest
     ProjectsIdBackgroundsUnsplashPost MimeJSON ModelsProject MimeJSON
projectsIdBackgroundsUnsplashPost BackgroundImage
project (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdBackgroundsUnsplashPost MimeJSON ModelsProject 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
id,ByteString
"/backgrounds/unsplash"]
    VikunjaRequest
  ProjectsIdBackgroundsUnsplashPost MimeJSON ModelsProject MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdBackgroundsUnsplashPost MimeJSON ModelsProject 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
  ProjectsIdBackgroundsUnsplashPost MimeJSON ModelsProject MimeJSON
-> BackgroundImage
-> VikunjaRequest
     ProjectsIdBackgroundsUnsplashPost MimeJSON ModelsProject 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` BackgroundImage
project

data ProjectsIdBackgroundsUnsplashPost 

-- | /Body Param/ "project" - The image you want to set as background
instance HasBodyParam ProjectsIdBackgroundsUnsplashPost BackgroundImage 

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

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


-- *** projectsIdBackgroundsUploadPut

-- | @PUT \/projects\/{id}\/backgrounds\/upload@
-- 
-- Upload a project background
-- 
-- Upload a project background.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdBackgroundsUploadPut
  :: (Consumes ProjectsIdBackgroundsUploadPut MimeMultipartFormData)
  => Background -- ^ "background" -  The file as single file.
  -> Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdBackgroundsUploadPut MimeMultipartFormData ModelsMessage MimeJSON
projectsIdBackgroundsUploadPut :: Background
-> Id
-> VikunjaRequest
     ProjectsIdBackgroundsUploadPut
     MimeMultipartFormData
     ModelsMessage
     MimeJSON
projectsIdBackgroundsUploadPut (Background Text
background) (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdBackgroundsUploadPut
     MimeMultipartFormData
     ModelsMessage
     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
"/backgrounds/upload"]
    VikunjaRequest
  ProjectsIdBackgroundsUploadPut
  MimeMultipartFormData
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdBackgroundsUploadPut
     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
  ProjectsIdBackgroundsUploadPut
  MimeMultipartFormData
  ModelsMessage
  MimeJSON
-> Part
-> VikunjaRequest
     ProjectsIdBackgroundsUploadPut
     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
"background" (MimeMultipartFormData -> Text -> ByteString
forall mtype x. MimeRender mtype x => mtype -> x -> ByteString
mimeRender' MimeMultipartFormData
MimeMultipartFormData Text
background)

data ProjectsIdBackgroundsUploadPut  

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

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


-- *** projectsIdDelete

-- | @DELETE \/projects\/{id}@
-- 
-- Deletes a project
-- 
-- Delets a project
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdDelete
  :: Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdDelete MimeNoContent ModelsMessage MimeJSON
projectsIdDelete :: Id
-> VikunjaRequest
     ProjectsIdDelete MimeNoContent ModelsMessage MimeJSON
projectsIdDelete (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdDelete 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
id]
    VikunjaRequest
  ProjectsIdDelete MimeNoContent ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdDelete 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 ProjectsIdDelete  
-- | @application/json@
instance Produces ProjectsIdDelete MimeJSON


-- *** projectsIdGet

-- | @GET \/projects\/{id}@
-- 
-- Gets one project
-- 
-- Returns a project by its ID.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdGet
  :: Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdGet MimeNoContent ModelsProject MimeJSON
projectsIdGet :: Id
-> VikunjaRequest
     ProjectsIdGet MimeNoContent ModelsProject MimeJSON
projectsIdGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdGet MimeNoContent ModelsProject 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]
    VikunjaRequest ProjectsIdGet MimeNoContent ModelsProject MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdGet MimeNoContent ModelsProject 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 ProjectsIdGet  
-- | @application/json@
instance Produces ProjectsIdGet MimeJSON


-- *** projectsIdPost

-- | @POST \/projects\/{id}@
-- 
-- Updates a project
-- 
-- Updates a project. This does not include adding a task (see below).
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdPost
  :: (Consumes ProjectsIdPost MimeJSON, MimeRender MimeJSON ModelsProject)
  => ModelsProject -- ^ "project" -  The project with updated values you want to update.
  -> Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdPost MimeJSON ModelsProject MimeJSON
projectsIdPost :: ModelsProject
-> Id
-> VikunjaRequest ProjectsIdPost MimeJSON ModelsProject MimeJSON
projectsIdPost ModelsProject
project (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest ProjectsIdPost MimeJSON ModelsProject 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
id]
    VikunjaRequest ProjectsIdPost MimeJSON ModelsProject MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest ProjectsIdPost MimeJSON ModelsProject 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 ProjectsIdPost MimeJSON ModelsProject MimeJSON
-> ModelsProject
-> VikunjaRequest ProjectsIdPost MimeJSON ModelsProject 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` ModelsProject
project

data ProjectsIdPost 

-- | /Body Param/ "project" - The project with updated values you want to update.
instance HasBodyParam ProjectsIdPost ModelsProject 

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

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


-- *** projectsIdProjectusersGet

-- | @GET \/projects\/{id}\/projectusers@
-- 
-- Get users
-- 
-- Lists all users (without emailadresses). Also possible to search for a specific user.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdProjectusersGet
  :: Id -- ^ "id" -  Project ID
  -> VikunjaRequest ProjectsIdProjectusersGet MimeNoContent [UserUser] MimeJSON
projectsIdProjectusersGet :: Id
-> VikunjaRequest
     ProjectsIdProjectusersGet MimeNoContent [UserUser] MimeJSON
projectsIdProjectusersGet (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdProjectusersGet MimeNoContent [UserUser] 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
"/projectusers"]
    VikunjaRequest
  ProjectsIdProjectusersGet MimeNoContent [UserUser] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdProjectusersGet 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 ProjectsIdProjectusersGet  

-- | /Optional Param/ "s" - Search for a user by its name.
instance HasOptionalParam ProjectsIdProjectusersGet S where
  applyOptionalParam :: VikunjaRequest ProjectsIdProjectusersGet contentType res accept
-> S
-> VikunjaRequest ProjectsIdProjectusersGet contentType res accept
applyOptionalParam VikunjaRequest ProjectsIdProjectusersGet contentType res accept
req (S Text
xs) =
    VikunjaRequest ProjectsIdProjectusersGet contentType res accept
req VikunjaRequest ProjectsIdProjectusersGet contentType res accept
-> [QueryItem]
-> VikunjaRequest ProjectsIdProjectusersGet 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 ProjectsIdProjectusersGet MimeJSON


-- *** projectsIdViewsViewBucketsGet

-- | @GET \/projects\/{id}\/views\/{view}\/buckets@
-- 
-- Get all kanban buckets of a project
-- 
-- Returns all kanban buckets which belong to that project. Buckets are always sorted by their `position` in ascending order. To get all buckets with their tasks, use the tasks endpoint with a kanban view.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdViewsViewBucketsGet
  :: Id -- ^ "id" -  Project ID
  -> View -- ^ "view" -  Project view ID
  -> VikunjaRequest ProjectsIdViewsViewBucketsGet MimeNoContent [ModelsBucket] MimeJSON
projectsIdViewsViewBucketsGet :: Id
-> View
-> VikunjaRequest
     ProjectsIdViewsViewBucketsGet MimeNoContent [ModelsBucket] MimeJSON
projectsIdViewsViewBucketsGet (Id Int
id) (View Int
view) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdViewsViewBucketsGet MimeNoContent [ModelsBucket] 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
"/buckets"]
    VikunjaRequest
  ProjectsIdViewsViewBucketsGet MimeNoContent [ModelsBucket] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdViewsViewBucketsGet MimeNoContent [ModelsBucket] 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 ProjectsIdViewsViewBucketsGet  
-- | @application/json@
instance Produces ProjectsIdViewsViewBucketsGet MimeJSON


-- *** projectsIdViewsViewBucketsPut

-- | @PUT \/projects\/{id}\/views\/{view}\/buckets@
-- 
-- Create a new bucket
-- 
-- Creates a new kanban bucket on a project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsIdViewsViewBucketsPut
  :: (Consumes ProjectsIdViewsViewBucketsPut MimeJSON, MimeRender MimeJSON ModelsBucket)
  => ModelsBucket -- ^ "bucket" -  The bucket object
  -> Id -- ^ "id" -  Project Id
  -> View -- ^ "view" -  Project view ID
  -> VikunjaRequest ProjectsIdViewsViewBucketsPut MimeJSON ModelsBucket MimeJSON
projectsIdViewsViewBucketsPut :: ModelsBucket
-> Id
-> View
-> VikunjaRequest
     ProjectsIdViewsViewBucketsPut MimeJSON ModelsBucket MimeJSON
projectsIdViewsViewBucketsPut ModelsBucket
bucket (Id Int
id) (View Int
view) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsIdViewsViewBucketsPut MimeJSON ModelsBucket 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
"/views/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
view,ByteString
"/buckets"]
    VikunjaRequest
  ProjectsIdViewsViewBucketsPut MimeJSON ModelsBucket MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsIdViewsViewBucketsPut MimeJSON ModelsBucket 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
  ProjectsIdViewsViewBucketsPut MimeJSON ModelsBucket MimeJSON
-> ModelsBucket
-> VikunjaRequest
     ProjectsIdViewsViewBucketsPut MimeJSON ModelsBucket 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` ModelsBucket
bucket

data ProjectsIdViewsViewBucketsPut 

-- | /Body Param/ "bucket" - The bucket object
instance HasBodyParam ProjectsIdViewsViewBucketsPut ModelsBucket 

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

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


-- *** projectsProjectIDDuplicatePut

-- | @PUT \/projects\/{projectID}\/duplicate@
-- 
-- Duplicate an existing project
-- 
-- Copies the project, tasks, files, kanban data, assignees, comments, attachments, lables, relations, backgrounds, user/team rights and link shares from one project to a new one. The user needs read access in the project and write access in the parent of the new project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectIDDuplicatePut
  :: (Consumes ProjectsProjectIDDuplicatePut MimeJSON, MimeRender MimeJSON ModelsProjectDuplicate)
  => ModelsProjectDuplicate -- ^ "project" -  The target parent project which should hold the copied project.
  -> ProjectId -- ^ "projectId" -  The project ID to duplicate
  -> VikunjaRequest ProjectsProjectIDDuplicatePut MimeJSON ModelsProjectDuplicate MimeJSON
projectsProjectIDDuplicatePut :: ModelsProjectDuplicate
-> ProjectId
-> VikunjaRequest
     ProjectsProjectIDDuplicatePut
     MimeJSON
     ModelsProjectDuplicate
     MimeJSON
projectsProjectIDDuplicatePut ModelsProjectDuplicate
project (ProjectId Int
projectId) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectIDDuplicatePut
     MimeJSON
     ModelsProjectDuplicate
     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
projectId,ByteString
"/duplicate"]
    VikunjaRequest
  ProjectsProjectIDDuplicatePut
  MimeJSON
  ModelsProjectDuplicate
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectIDDuplicatePut
     MimeJSON
     ModelsProjectDuplicate
     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
  ProjectsProjectIDDuplicatePut
  MimeJSON
  ModelsProjectDuplicate
  MimeJSON
-> ModelsProjectDuplicate
-> VikunjaRequest
     ProjectsProjectIDDuplicatePut
     MimeJSON
     ModelsProjectDuplicate
     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` ModelsProjectDuplicate
project

data ProjectsProjectIDDuplicatePut 

-- | /Body Param/ "project" - The target parent project which should hold the copied project.
instance HasBodyParam ProjectsProjectIDDuplicatePut ModelsProjectDuplicate 

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

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


-- *** projectsProjectIDViewsViewBucketsBucketIDDelete

-- | @DELETE \/projects\/{projectID}\/views\/{view}\/buckets\/{bucketID}@
-- 
-- Deletes an existing bucket
-- 
-- Deletes an existing kanban bucket and dissociates all of its task. It does not delete any tasks. You cannot delete the last bucket on a project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectIDViewsViewBucketsBucketIDDelete
  :: ProjectId -- ^ "projectId" -  Project Id
  -> BucketId -- ^ "bucketId" -  Bucket Id
  -> View -- ^ "view" -  Project view ID
  -> VikunjaRequest ProjectsProjectIDViewsViewBucketsBucketIDDelete MimeNoContent ModelsMessage MimeJSON
projectsProjectIDViewsViewBucketsBucketIDDelete :: ProjectId
-> BucketId
-> View
-> VikunjaRequest
     ProjectsProjectIDViewsViewBucketsBucketIDDelete
     MimeNoContent
     ModelsMessage
     MimeJSON
projectsProjectIDViewsViewBucketsBucketIDDelete (ProjectId Int
projectId) (BucketId Int
bucketId) (View Int
view) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectIDViewsViewBucketsBucketIDDelete
     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
"/views/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
view,ByteString
"/buckets/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
bucketId]
    VikunjaRequest
  ProjectsProjectIDViewsViewBucketsBucketIDDelete
  MimeNoContent
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectIDViewsViewBucketsBucketIDDelete
     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 ProjectsProjectIDViewsViewBucketsBucketIDDelete  
-- | @application/json@
instance Produces ProjectsProjectIDViewsViewBucketsBucketIDDelete MimeJSON


-- *** projectsProjectIDViewsViewBucketsBucketIDPost

-- | @POST \/projects\/{projectID}\/views\/{view}\/buckets\/{bucketID}@
-- 
-- Update an existing bucket
-- 
-- Updates an existing kanban bucket.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectIDViewsViewBucketsBucketIDPost
  :: (Consumes ProjectsProjectIDViewsViewBucketsBucketIDPost MimeJSON, MimeRender MimeJSON ModelsBucket)
  => ModelsBucket -- ^ "bucket" -  The bucket object
  -> ProjectId -- ^ "projectId" -  Project Id
  -> BucketId -- ^ "bucketId" -  Bucket Id
  -> View -- ^ "view" -  Project view ID
  -> VikunjaRequest ProjectsProjectIDViewsViewBucketsBucketIDPost MimeJSON ModelsBucket MimeJSON
projectsProjectIDViewsViewBucketsBucketIDPost :: ModelsBucket
-> ProjectId
-> BucketId
-> View
-> VikunjaRequest
     ProjectsProjectIDViewsViewBucketsBucketIDPost
     MimeJSON
     ModelsBucket
     MimeJSON
projectsProjectIDViewsViewBucketsBucketIDPost ModelsBucket
bucket (ProjectId Int
projectId) (BucketId Int
bucketId) (View Int
view) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectIDViewsViewBucketsBucketIDPost
     MimeJSON
     ModelsBucket
     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
"/views/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
view,ByteString
"/buckets/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
bucketId]
    VikunjaRequest
  ProjectsProjectIDViewsViewBucketsBucketIDPost
  MimeJSON
  ModelsBucket
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectIDViewsViewBucketsBucketIDPost
     MimeJSON
     ModelsBucket
     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
  ProjectsProjectIDViewsViewBucketsBucketIDPost
  MimeJSON
  ModelsBucket
  MimeJSON
-> ModelsBucket
-> VikunjaRequest
     ProjectsProjectIDViewsViewBucketsBucketIDPost
     MimeJSON
     ModelsBucket
     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` ModelsBucket
bucket

data ProjectsProjectIDViewsViewBucketsBucketIDPost 

-- | /Body Param/ "bucket" - The bucket object
instance HasBodyParam ProjectsProjectIDViewsViewBucketsBucketIDPost ModelsBucket 

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

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


-- *** projectsProjectViewsGet

-- | @GET \/projects\/{project}\/views@
-- 
-- Get all project views for a project
-- 
-- Returns all project views for a sepcific project
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectViewsGet
  :: Project -- ^ "project" -  Project ID
  -> VikunjaRequest ProjectsProjectViewsGet MimeNoContent [ModelsProjectView] MimeJSON
projectsProjectViewsGet :: Project
-> VikunjaRequest
     ProjectsProjectViewsGet MimeNoContent [ModelsProjectView] MimeJSON
projectsProjectViewsGet (Project Int
project) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectViewsGet MimeNoContent [ModelsProjectView] 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
"/views"]
    VikunjaRequest
  ProjectsProjectViewsGet MimeNoContent [ModelsProjectView] MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectViewsGet MimeNoContent [ModelsProjectView] 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 ProjectsProjectViewsGet  
-- | @application/json@
instance Produces ProjectsProjectViewsGet MimeJSON


-- *** projectsProjectViewsIdDelete

-- | @DELETE \/projects\/{project}\/views\/{id}@
-- 
-- Delete a project view
-- 
-- Deletes a project view.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectViewsIdDelete
  :: Project -- ^ "project" -  Project ID
  -> Id -- ^ "id" -  Project View ID
  -> VikunjaRequest ProjectsProjectViewsIdDelete MimeNoContent ModelsMessage MimeJSON
projectsProjectViewsIdDelete :: Project
-> Id
-> VikunjaRequest
     ProjectsProjectViewsIdDelete MimeNoContent ModelsMessage MimeJSON
projectsProjectViewsIdDelete (Project Int
project) (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectViewsIdDelete 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
"/views/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    VikunjaRequest
  ProjectsProjectViewsIdDelete MimeNoContent ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectViewsIdDelete 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 ProjectsProjectViewsIdDelete  
-- | @application/json@
instance Produces ProjectsProjectViewsIdDelete MimeJSON


-- *** projectsProjectViewsIdGet

-- | @GET \/projects\/{project}\/views\/{id}@
-- 
-- Get one project view
-- 
-- Returns a project view by its ID.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectViewsIdGet
  :: Project -- ^ "project" -  Project ID
  -> Id -- ^ "id" -  Project View ID
  -> VikunjaRequest ProjectsProjectViewsIdGet MimeNoContent ModelsProjectView MimeJSON
projectsProjectViewsIdGet :: Project
-> Id
-> VikunjaRequest
     ProjectsProjectViewsIdGet MimeNoContent ModelsProjectView MimeJSON
projectsProjectViewsIdGet (Project Int
project) (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectViewsIdGet MimeNoContent ModelsProjectView 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
"/views/",Int -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Int
id]
    VikunjaRequest
  ProjectsProjectViewsIdGet MimeNoContent ModelsProjectView MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectViewsIdGet MimeNoContent ModelsProjectView 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 ProjectsProjectViewsIdGet  
-- | @application/json@
instance Produces ProjectsProjectViewsIdGet MimeJSON


-- *** projectsProjectViewsIdPost

-- | @POST \/projects\/{project}\/views\/{id}@
-- 
-- Updates a project view
-- 
-- Updates a project view.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectViewsIdPost
  :: (Consumes ProjectsProjectViewsIdPost MimeJSON, MimeRender MimeJSON ModelsProjectView)
  => ModelsProjectView -- ^ "view" -  The project view with updated values you want to change.
  -> Project -- ^ "project" -  Project ID
  -> Id -- ^ "id" -  Project View ID
  -> VikunjaRequest ProjectsProjectViewsIdPost MimeJSON ModelsProjectView MimeJSON
projectsProjectViewsIdPost :: ModelsProjectView
-> Project
-> Id
-> VikunjaRequest
     ProjectsProjectViewsIdPost MimeJSON ModelsProjectView MimeJSON
projectsProjectViewsIdPost ModelsProjectView
view (Project Int
project) (Id Int
id) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectViewsIdPost MimeJSON ModelsProjectView 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
id]
    VikunjaRequest
  ProjectsProjectViewsIdPost MimeJSON ModelsProjectView MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectViewsIdPost MimeJSON ModelsProjectView 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
  ProjectsProjectViewsIdPost MimeJSON ModelsProjectView MimeJSON
-> ModelsProjectView
-> VikunjaRequest
     ProjectsProjectViewsIdPost MimeJSON ModelsProjectView 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` ModelsProjectView
view

data ProjectsProjectViewsIdPost 

-- | /Body Param/ "view" - The project view with updated values you want to change.
instance HasBodyParam ProjectsProjectViewsIdPost ModelsProjectView 

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

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


-- *** projectsProjectViewsPut

-- | @PUT \/projects\/{project}\/views@
-- 
-- Create a project view
-- 
-- Create a project view in a specific project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsProjectViewsPut
  :: (Consumes ProjectsProjectViewsPut MimeJSON, MimeRender MimeJSON ModelsProjectView)
  => ModelsProjectView -- ^ "view" -  The project view you want to create.
  -> Project -- ^ "project" -  Project ID
  -> VikunjaRequest ProjectsProjectViewsPut MimeJSON ModelsProjectView MimeJSON
projectsProjectViewsPut :: ModelsProjectView
-> Project
-> VikunjaRequest
     ProjectsProjectViewsPut MimeJSON ModelsProjectView MimeJSON
projectsProjectViewsPut ModelsProjectView
view (Project Int
project) =
  Method
-> [ByteString]
-> VikunjaRequest
     ProjectsProjectViewsPut MimeJSON ModelsProjectView 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
"/views"]
    VikunjaRequest
  ProjectsProjectViewsPut MimeJSON ModelsProjectView MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     ProjectsProjectViewsPut MimeJSON ModelsProjectView 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
  ProjectsProjectViewsPut MimeJSON ModelsProjectView MimeJSON
-> ModelsProjectView
-> VikunjaRequest
     ProjectsProjectViewsPut MimeJSON ModelsProjectView 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` ModelsProjectView
view

data ProjectsProjectViewsPut 

-- | /Body Param/ "view" - The project view you want to create.
instance HasBodyParam ProjectsProjectViewsPut ModelsProjectView 

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

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


-- *** projectsPut

-- | @PUT \/projects@
-- 
-- Creates a new project
-- 
-- Creates a new project. If a parent project is provided the user needs to have write access to that project.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
projectsPut
  :: (Consumes ProjectsPut MimeJSON, MimeRender MimeJSON ModelsProject)
  => ModelsProject -- ^ "project" -  The project you want to create.
  -> VikunjaRequest ProjectsPut MimeJSON ModelsProject MimeJSON
projectsPut :: ModelsProject
-> VikunjaRequest ProjectsPut MimeJSON ModelsProject MimeJSON
projectsPut ModelsProject
project =
  Method
-> [ByteString]
-> VikunjaRequest ProjectsPut MimeJSON ModelsProject MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/projects"]
    VikunjaRequest ProjectsPut MimeJSON ModelsProject MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest ProjectsPut MimeJSON ModelsProject 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 ProjectsPut MimeJSON ModelsProject MimeJSON
-> ModelsProject
-> VikunjaRequest ProjectsPut MimeJSON ModelsProject 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` ModelsProject
project

data ProjectsPut 

-- | /Body Param/ "project" - The project you want to create.
instance HasBodyParam ProjectsPut ModelsProject 

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

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