{-# 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
backgroundsUnsplashImageImageGet
:: Image
-> 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
instance Produces BackgroundsUnsplashImageImageGet MimeOctetStream
backgroundsUnsplashImageImageThumbGet
:: Image
-> 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
instance Produces BackgroundsUnsplashImageImageThumbGet MimeOctetStream
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
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)
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)
instance Produces BackgroundsUnsplashSearchGet MimeJSON
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
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)
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)
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)
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)
instance Produces ProjectsGet MimeJSON
projectsIdBackgroundDelete
:: 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
instance Produces ProjectsIdBackgroundDelete MimeJSON
projectsIdBackgroundGet
:: 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
instance Produces ProjectsIdBackgroundGet MimeOctetStream
projectsIdBackgroundsUnsplashPost
:: (Consumes ProjectsIdBackgroundsUnsplashPost MimeJSON, MimeRender MimeJSON BackgroundImage)
=> BackgroundImage
-> 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
instance HasBodyParam ProjectsIdBackgroundsUnsplashPost BackgroundImage
instance Consumes ProjectsIdBackgroundsUnsplashPost MimeJSON
instance Produces ProjectsIdBackgroundsUnsplashPost MimeJSON
projectsIdBackgroundsUploadPut
:: (Consumes ProjectsIdBackgroundsUploadPut MimeMultipartFormData)
=> Background
-> 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
instance Consumes ProjectsIdBackgroundsUploadPut MimeMultipartFormData
instance Produces ProjectsIdBackgroundsUploadPut MimeJSON
projectsIdDelete
:: 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
instance Produces ProjectsIdDelete MimeJSON
projectsIdGet
:: 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
instance Produces ProjectsIdGet MimeJSON
projectsIdPost
:: (Consumes ProjectsIdPost MimeJSON, MimeRender MimeJSON ModelsProject)
=> ModelsProject
-> 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
instance HasBodyParam ProjectsIdPost ModelsProject
instance Consumes ProjectsIdPost MimeJSON
instance Produces ProjectsIdPost MimeJSON
projectsIdProjectusersGet
:: 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
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)
instance Produces ProjectsIdProjectusersGet MimeJSON
projectsIdViewsViewBucketsGet
:: Id
-> View
-> 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
instance Produces ProjectsIdViewsViewBucketsGet MimeJSON
projectsIdViewsViewBucketsPut
:: (Consumes ProjectsIdViewsViewBucketsPut MimeJSON, MimeRender MimeJSON ModelsBucket)
=> ModelsBucket
-> Id
-> View
-> 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
instance HasBodyParam ProjectsIdViewsViewBucketsPut ModelsBucket
instance Consumes ProjectsIdViewsViewBucketsPut MimeJSON
instance Produces ProjectsIdViewsViewBucketsPut MimeJSON
projectsProjectIDDuplicatePut
:: (Consumes ProjectsProjectIDDuplicatePut MimeJSON, MimeRender MimeJSON ModelsProjectDuplicate)
=> ModelsProjectDuplicate
-> ProjectId
-> 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
instance HasBodyParam ProjectsProjectIDDuplicatePut ModelsProjectDuplicate
instance Consumes ProjectsProjectIDDuplicatePut MimeJSON
instance Produces ProjectsProjectIDDuplicatePut MimeJSON
projectsProjectIDViewsViewBucketsBucketIDDelete
:: ProjectId
-> BucketId
-> View
-> 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
instance Produces ProjectsProjectIDViewsViewBucketsBucketIDDelete MimeJSON
projectsProjectIDViewsViewBucketsBucketIDPost
:: (Consumes ProjectsProjectIDViewsViewBucketsBucketIDPost MimeJSON, MimeRender MimeJSON ModelsBucket)
=> ModelsBucket
-> ProjectId
-> BucketId
-> View
-> 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
instance HasBodyParam ProjectsProjectIDViewsViewBucketsBucketIDPost ModelsBucket
instance Consumes ProjectsProjectIDViewsViewBucketsBucketIDPost MimeJSON
instance Produces ProjectsProjectIDViewsViewBucketsBucketIDPost MimeJSON
projectsProjectViewsGet
:: Project
-> 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
instance Produces ProjectsProjectViewsGet MimeJSON
projectsProjectViewsIdDelete
:: Project
-> 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
instance Produces ProjectsProjectViewsIdDelete MimeJSON
projectsProjectViewsIdGet
:: Project
-> 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
instance Produces ProjectsProjectViewsIdGet MimeJSON
projectsProjectViewsIdPost
:: (Consumes ProjectsProjectViewsIdPost MimeJSON, MimeRender MimeJSON ModelsProjectView)
=> ModelsProjectView
-> Project
-> 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
instance HasBodyParam ProjectsProjectViewsIdPost ModelsProjectView
instance Consumes ProjectsProjectViewsIdPost MimeJSON
instance Produces ProjectsProjectViewsIdPost MimeJSON
projectsProjectViewsPut
:: (Consumes ProjectsProjectViewsPut MimeJSON, MimeRender MimeJSON ModelsProjectView)
=> ModelsProjectView
-> Project
-> 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
instance HasBodyParam ProjectsProjectViewsPut ModelsProjectView
instance Consumes ProjectsProjectViewsPut MimeJSON
instance Produces ProjectsProjectViewsPut MimeJSON
projectsPut
:: (Consumes ProjectsPut MimeJSON, MimeRender MimeJSON ModelsProject)
=> ModelsProject
-> 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
instance HasBodyParam ProjectsPut ModelsProject
instance Consumes ProjectsPut MimeJSON
instance Produces ProjectsPut MimeJSON