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

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


-- ** Migration

-- *** migrationMicrosoftTodoAuthGet

-- | @GET \/migration\/microsoft-todo\/auth@
-- 
-- Get the auth url from Microsoft Todo
-- 
-- Returns the auth url where the user needs to get its auth code. This code can then be used to migrate everything from Microsoft Todo to Vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationMicrosoftTodoAuthGet
  :: VikunjaRequest MigrationMicrosoftTodoAuthGet MimeNoContent HandlerAuthURL MimeJSON
migrationMicrosoftTodoAuthGet :: VikunjaRequest
  MigrationMicrosoftTodoAuthGet MimeNoContent HandlerAuthURL MimeJSON
migrationMicrosoftTodoAuthGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationMicrosoftTodoAuthGet MimeNoContent HandlerAuthURL MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/microsoft-todo/auth"]
    VikunjaRequest
  MigrationMicrosoftTodoAuthGet MimeNoContent HandlerAuthURL MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationMicrosoftTodoAuthGet MimeNoContent HandlerAuthURL 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 MigrationMicrosoftTodoAuthGet  
-- | @application/json@
instance Produces MigrationMicrosoftTodoAuthGet MimeJSON


-- *** migrationMicrosoftTodoMigratePost

-- | @POST \/migration\/microsoft-todo\/migrate@
-- 
-- Migrate all projects, tasks etc. from Microsoft Todo
-- 
-- Migrates all tasklinsts, tasks, notes and reminders from Microsoft Todo to Vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationMicrosoftTodoMigratePost
  :: (Consumes MigrationMicrosoftTodoMigratePost MimeJSON, MimeRender MimeJSON MicrosofttodoMigration)
  => MicrosofttodoMigration -- ^ "migrationCode" -  The auth token previously obtained from the auth url. See the docs for /migration/microsoft-todo/auth.
  -> VikunjaRequest MigrationMicrosoftTodoMigratePost MimeJSON ModelsMessage MimeJSON
migrationMicrosoftTodoMigratePost :: MicrosofttodoMigration
-> VikunjaRequest
     MigrationMicrosoftTodoMigratePost MimeJSON ModelsMessage MimeJSON
migrationMicrosoftTodoMigratePost MicrosofttodoMigration
migrationCode =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationMicrosoftTodoMigratePost MimeJSON ModelsMessage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/migration/microsoft-todo/migrate"]
    VikunjaRequest
  MigrationMicrosoftTodoMigratePost MimeJSON ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationMicrosoftTodoMigratePost MimeJSON ModelsMessage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)
    VikunjaRequest
  MigrationMicrosoftTodoMigratePost MimeJSON ModelsMessage MimeJSON
-> MicrosofttodoMigration
-> VikunjaRequest
     MigrationMicrosoftTodoMigratePost MimeJSON ModelsMessage MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
VikunjaRequest req contentType res accept
-> param -> VikunjaRequest req contentType res accept
`setBodyParam` MicrosofttodoMigration
migrationCode

data MigrationMicrosoftTodoMigratePost 

-- | /Body Param/ "migrationCode" - The auth token previously obtained from the auth url. See the docs for /migration/microsoft-todo/auth.
instance HasBodyParam MigrationMicrosoftTodoMigratePost MicrosofttodoMigration 

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

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


-- *** migrationMicrosoftTodoStatusGet

-- | @GET \/migration\/microsoft-todo\/status@
-- 
-- Get migration status
-- 
-- Returns if the current user already did the migation or not. This is useful to show a confirmation message in the frontend if the user is trying to do the same migration again.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationMicrosoftTodoStatusGet
  :: VikunjaRequest MigrationMicrosoftTodoStatusGet MimeNoContent MigrationStatus MimeJSON
migrationMicrosoftTodoStatusGet :: VikunjaRequest
  MigrationMicrosoftTodoStatusGet
  MimeNoContent
  MigrationStatus
  MimeJSON
migrationMicrosoftTodoStatusGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationMicrosoftTodoStatusGet
     MimeNoContent
     MigrationStatus
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/microsoft-todo/status"]
    VikunjaRequest
  MigrationMicrosoftTodoStatusGet
  MimeNoContent
  MigrationStatus
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationMicrosoftTodoStatusGet
     MimeNoContent
     MigrationStatus
     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 MigrationMicrosoftTodoStatusGet  
-- | @application/json@
instance Produces MigrationMicrosoftTodoStatusGet MimeJSON


-- *** migrationTicktickMigratePost

-- | @POST \/migration\/ticktick\/migrate@
-- 
-- Import all projects, tasks etc. from a TickTick backup export
-- 
-- Imports all projects, tasks, notes, reminders, subtasks and files from a TickTick backup export into Vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTicktickMigratePost
  :: (Consumes MigrationTicktickMigratePost MimeFormUrlEncoded)
  => ParamImport -- ^ "_import" -  The TickTick backup csv file.
  -> VikunjaRequest MigrationTicktickMigratePost MimeFormUrlEncoded ModelsMessage MimeJSON
migrationTicktickMigratePost :: ParamImport
-> VikunjaRequest
     MigrationTicktickMigratePost
     MimeFormUrlEncoded
     ModelsMessage
     MimeJSON
migrationTicktickMigratePost (ParamImport Text
_import) =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTicktickMigratePost
     MimeFormUrlEncoded
     ModelsMessage
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/migration/ticktick/migrate"]
    VikunjaRequest
  MigrationTicktickMigratePost
  MimeFormUrlEncoded
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTicktickMigratePost
     MimeFormUrlEncoded
     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
  MigrationTicktickMigratePost
  MimeFormUrlEncoded
  ModelsMessage
  MimeJSON
-> Form
-> VikunjaRequest
     MigrationTicktickMigratePost
     MimeFormUrlEncoded
     ModelsMessage
     MimeJSON
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> Form -> VikunjaRequest req contentType res accept
`addForm` (Method, Text) -> Form
forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"import", Text
_import)

data MigrationTicktickMigratePost  

-- | @application/x-www-form-urlencoded@
instance Consumes MigrationTicktickMigratePost MimeFormUrlEncoded

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


-- *** migrationTicktickStatusGet

-- | @GET \/migration\/ticktick\/status@
-- 
-- Get migration status
-- 
-- Returns if the current user already did the migation or not. This is useful to show a confirmation message in the frontend if the user is trying to do the same migration again.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTicktickStatusGet
  :: VikunjaRequest MigrationTicktickStatusGet MimeNoContent MigrationStatus MimeJSON
migrationTicktickStatusGet :: VikunjaRequest
  MigrationTicktickStatusGet MimeNoContent MigrationStatus MimeJSON
migrationTicktickStatusGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTicktickStatusGet MimeNoContent MigrationStatus MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/ticktick/status"]
    VikunjaRequest
  MigrationTicktickStatusGet MimeNoContent MigrationStatus MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTicktickStatusGet MimeNoContent MigrationStatus 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 MigrationTicktickStatusGet  
-- | @application/json@
instance Produces MigrationTicktickStatusGet MimeJSON


-- *** migrationTodoistAuthGet

-- | @GET \/migration\/todoist\/auth@
-- 
-- Get the auth url from todoist
-- 
-- Returns the auth url where the user needs to get its auth code. This code can then be used to migrate everything from todoist to Vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTodoistAuthGet
  :: VikunjaRequest MigrationTodoistAuthGet MimeNoContent HandlerAuthURL MimeJSON
migrationTodoistAuthGet :: VikunjaRequest
  MigrationTodoistAuthGet MimeNoContent HandlerAuthURL MimeJSON
migrationTodoistAuthGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTodoistAuthGet MimeNoContent HandlerAuthURL MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/todoist/auth"]
    VikunjaRequest
  MigrationTodoistAuthGet MimeNoContent HandlerAuthURL MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTodoistAuthGet MimeNoContent HandlerAuthURL 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 MigrationTodoistAuthGet  
-- | @application/json@
instance Produces MigrationTodoistAuthGet MimeJSON


-- *** migrationTodoistMigratePost

-- | @POST \/migration\/todoist\/migrate@
-- 
-- Migrate all lists, tasks etc. from todoist
-- 
-- Migrates all projects, tasks, notes, reminders, subtasks and files from todoist to vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTodoistMigratePost
  :: (Consumes MigrationTodoistMigratePost MimeJSON, MimeRender MimeJSON TodoistMigration)
  => TodoistMigration -- ^ "migrationCode" -  The auth code previously obtained from the auth url. See the docs for /migration/todoist/auth.
  -> VikunjaRequest MigrationTodoistMigratePost MimeJSON ModelsMessage MimeJSON
migrationTodoistMigratePost :: TodoistMigration
-> VikunjaRequest
     MigrationTodoistMigratePost MimeJSON ModelsMessage MimeJSON
migrationTodoistMigratePost TodoistMigration
migrationCode =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTodoistMigratePost MimeJSON ModelsMessage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/migration/todoist/migrate"]
    VikunjaRequest
  MigrationTodoistMigratePost MimeJSON ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTodoistMigratePost MimeJSON ModelsMessage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)
    VikunjaRequest
  MigrationTodoistMigratePost MimeJSON ModelsMessage MimeJSON
-> TodoistMigration
-> VikunjaRequest
     MigrationTodoistMigratePost MimeJSON ModelsMessage MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
VikunjaRequest req contentType res accept
-> param -> VikunjaRequest req contentType res accept
`setBodyParam` TodoistMigration
migrationCode

data MigrationTodoistMigratePost 

-- | /Body Param/ "migrationCode" - The auth code previously obtained from the auth url. See the docs for /migration/todoist/auth.
instance HasBodyParam MigrationTodoistMigratePost TodoistMigration 

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

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


-- *** migrationTodoistStatusGet

-- | @GET \/migration\/todoist\/status@
-- 
-- Get migration status
-- 
-- Returns if the current user already did the migation or not. This is useful to show a confirmation message in the frontend if the user is trying to do the same migration again.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTodoistStatusGet
  :: VikunjaRequest MigrationTodoistStatusGet MimeNoContent MigrationStatus MimeJSON
migrationTodoistStatusGet :: VikunjaRequest
  MigrationTodoistStatusGet MimeNoContent MigrationStatus MimeJSON
migrationTodoistStatusGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTodoistStatusGet MimeNoContent MigrationStatus MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/todoist/status"]
    VikunjaRequest
  MigrationTodoistStatusGet MimeNoContent MigrationStatus MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTodoistStatusGet MimeNoContent MigrationStatus 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 MigrationTodoistStatusGet  
-- | @application/json@
instance Produces MigrationTodoistStatusGet MimeJSON


-- *** migrationTrelloAuthGet

-- | @GET \/migration\/trello\/auth@
-- 
-- Get the auth url from trello
-- 
-- Returns the auth url where the user needs to get its auth code. This code can then be used to migrate everything from trello to Vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTrelloAuthGet
  :: VikunjaRequest MigrationTrelloAuthGet MimeNoContent HandlerAuthURL MimeJSON
migrationTrelloAuthGet :: VikunjaRequest
  MigrationTrelloAuthGet MimeNoContent HandlerAuthURL MimeJSON
migrationTrelloAuthGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTrelloAuthGet MimeNoContent HandlerAuthURL MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/trello/auth"]
    VikunjaRequest
  MigrationTrelloAuthGet MimeNoContent HandlerAuthURL MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTrelloAuthGet MimeNoContent HandlerAuthURL 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 MigrationTrelloAuthGet  
-- | @application/json@
instance Produces MigrationTrelloAuthGet MimeJSON


-- *** migrationTrelloMigratePost

-- | @POST \/migration\/trello\/migrate@
-- 
-- Migrate all projects, tasks etc. from trello
-- 
-- Migrates all projects, tasks, notes, reminders, subtasks and files from trello to vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTrelloMigratePost
  :: (Consumes MigrationTrelloMigratePost MimeJSON, MimeRender MimeJSON TrelloMigration)
  => TrelloMigration -- ^ "migrationCode" -  The auth token previously obtained from the auth url. See the docs for /migration/trello/auth.
  -> VikunjaRequest MigrationTrelloMigratePost MimeJSON ModelsMessage MimeJSON
migrationTrelloMigratePost :: TrelloMigration
-> VikunjaRequest
     MigrationTrelloMigratePost MimeJSON ModelsMessage MimeJSON
migrationTrelloMigratePost TrelloMigration
migrationCode =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTrelloMigratePost MimeJSON ModelsMessage MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/migration/trello/migrate"]
    VikunjaRequest
  MigrationTrelloMigratePost MimeJSON ModelsMessage MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTrelloMigratePost MimeJSON ModelsMessage MimeJSON
forall authMethod req contentType res accept.
AuthMethod authMethod =>
VikunjaRequest req contentType res accept
-> Proxy authMethod -> VikunjaRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyJWTKeyAuth
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyJWTKeyAuth)
    VikunjaRequest
  MigrationTrelloMigratePost MimeJSON ModelsMessage MimeJSON
-> TrelloMigration
-> VikunjaRequest
     MigrationTrelloMigratePost MimeJSON ModelsMessage MimeJSON
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
VikunjaRequest req contentType res accept
-> param -> VikunjaRequest req contentType res accept
`setBodyParam` TrelloMigration
migrationCode

data MigrationTrelloMigratePost 

-- | /Body Param/ "migrationCode" - The auth token previously obtained from the auth url. See the docs for /migration/trello/auth.
instance HasBodyParam MigrationTrelloMigratePost TrelloMigration 

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

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


-- *** migrationTrelloStatusGet

-- | @GET \/migration\/trello\/status@
-- 
-- Get migration status
-- 
-- Returns if the current user already did the migation or not. This is useful to show a confirmation message in the frontend if the user is trying to do the same migration again.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationTrelloStatusGet
  :: VikunjaRequest MigrationTrelloStatusGet MimeNoContent MigrationStatus MimeJSON
migrationTrelloStatusGet :: VikunjaRequest
  MigrationTrelloStatusGet MimeNoContent MigrationStatus MimeJSON
migrationTrelloStatusGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationTrelloStatusGet MimeNoContent MigrationStatus MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/trello/status"]
    VikunjaRequest
  MigrationTrelloStatusGet MimeNoContent MigrationStatus MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationTrelloStatusGet MimeNoContent MigrationStatus 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 MigrationTrelloStatusGet  
-- | @application/json@
instance Produces MigrationTrelloStatusGet MimeJSON


-- *** migrationVikunjaFileMigratePost

-- | @POST \/migration\/vikunja-file\/migrate@
-- 
-- Import all projects, tasks etc. from a Vikunja data export
-- 
-- Imports all projects, tasks, notes, reminders, subtasks and files from a Vikunjda data export into Vikunja.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationVikunjaFileMigratePost
  :: (Consumes MigrationVikunjaFileMigratePost MimeFormUrlEncoded)
  => ParamImport -- ^ "_import" -  The Vikunja export zip file.
  -> VikunjaRequest MigrationVikunjaFileMigratePost MimeFormUrlEncoded ModelsMessage MimeJSON
migrationVikunjaFileMigratePost :: ParamImport
-> VikunjaRequest
     MigrationVikunjaFileMigratePost
     MimeFormUrlEncoded
     ModelsMessage
     MimeJSON
migrationVikunjaFileMigratePost (ParamImport Text
_import) =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationVikunjaFileMigratePost
     MimeFormUrlEncoded
     ModelsMessage
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/migration/vikunja-file/migrate"]
    VikunjaRequest
  MigrationVikunjaFileMigratePost
  MimeFormUrlEncoded
  ModelsMessage
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationVikunjaFileMigratePost
     MimeFormUrlEncoded
     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
  MigrationVikunjaFileMigratePost
  MimeFormUrlEncoded
  ModelsMessage
  MimeJSON
-> Form
-> VikunjaRequest
     MigrationVikunjaFileMigratePost
     MimeFormUrlEncoded
     ModelsMessage
     MimeJSON
forall req contentType res accept.
VikunjaRequest req contentType res accept
-> Form -> VikunjaRequest req contentType res accept
`addForm` (Method, Text) -> Form
forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"import", Text
_import)

data MigrationVikunjaFileMigratePost  

-- | @application/x-www-form-urlencoded@
instance Consumes MigrationVikunjaFileMigratePost MimeFormUrlEncoded

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


-- *** migrationVikunjaFileStatusGet

-- | @GET \/migration\/vikunja-file\/status@
-- 
-- Get migration status
-- 
-- Returns if the current user already did the migation or not. This is useful to show a confirmation message in the frontend if the user is trying to do the same migration again.
-- 
-- AuthMethod: 'AuthApiKeyJWTKeyAuth'
-- 
migrationVikunjaFileStatusGet
  :: VikunjaRequest MigrationVikunjaFileStatusGet MimeNoContent MigrationStatus MimeJSON
migrationVikunjaFileStatusGet :: VikunjaRequest
  MigrationVikunjaFileStatusGet
  MimeNoContent
  MigrationStatus
  MimeJSON
migrationVikunjaFileStatusGet =
  Method
-> [ByteString]
-> VikunjaRequest
     MigrationVikunjaFileStatusGet
     MimeNoContent
     MigrationStatus
     MimeJSON
forall req contentType res accept.
Method -> [ByteString] -> VikunjaRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/migration/vikunja-file/status"]
    VikunjaRequest
  MigrationVikunjaFileStatusGet
  MimeNoContent
  MigrationStatus
  MimeJSON
-> Proxy AuthApiKeyJWTKeyAuth
-> VikunjaRequest
     MigrationVikunjaFileStatusGet
     MimeNoContent
     MigrationStatus
     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 MigrationVikunjaFileStatusGet  
-- | @application/json@
instance Produces MigrationVikunjaFileStatusGet MimeJSON