{-
   BitMEX API

   ## REST API for the BitMEX Trading Platform  [View Changelog](/app/apiChangelog)    #### Getting Started   ##### Fetching Data  All REST endpoints are documented below. You can try out any query right from this interface.  Most table queries accept `count`, `start`, and `reverse` params. Set `reverse=true` to get rows newest-first.  Additional documentation regarding filters, timestamps, and authentication is available in [the main API documentation](https://www.bitmex.com/app/restAPI).  *All* table data is available via the [Websocket](/app/wsAPI). We highly recommend using the socket if you want to have the quickest possible data without being subject to ratelimits.  ##### Return Types  By default, all data is returned as JSON. Send `?_format=csv` to get CSV data or `?_format=xml` to get XML data.  ##### Trade Data Queries  *This is only a small subset of what is available, to get you started.*  Fill in the parameters and click the `Try it out!` button to try any of these queries.  * [Pricing Data](#!/Quote/Quote_get)  * [Trade Data](#!/Trade/Trade_get)  * [OrderBook Data](#!/OrderBook/OrderBook_getL2)  * [Settlement Data](#!/Settlement/Settlement_get)  * [Exchange Statistics](#!/Stats/Stats_history)  Every function of the BitMEX.com platform is exposed here and documented. Many more functions are available.  ##### Swagger Specification  [⇩ Download Swagger JSON](swagger.json)    ## All API Endpoints  Click to expand a section. 

   OpenAPI spec version: 2.0
   BitMEX API API version: 1.2.0
   Contact: support@bitmex.com
   Generated by Swagger Codegen (https://github.com/swagger-api/swagger-codegen.git)
-}

{-|
Module : BitMEX.API
-}

{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}

module BitMEX.API where

import BitMEX.Core
import BitMEX.MimeTypes
import BitMEX.Model as M

import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Char8 as BC
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 GHC.Base as P (Alternative)
import qualified Lens.Micro as L
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.Monoid ((<>))
import Data.Function ((&))
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


-- ** APIKey

-- *** aPIKeyDisable

-- | @POST \/apiKey\/disable@
-- 
-- Disable an API Key.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
aPIKeyDisable
  :: (Consumes APIKeyDisable contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> ApiKeyId -- ^ "apiKeyId" -  API Key ID (public component).
  -> BitMEXRequest APIKeyDisable contentType APIKey accept
aPIKeyDisable _  _ (ApiKeyId apiKeyId) =
  _mkRequest "POST" ["/apiKey/disable"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("apiKeyID", apiKeyId)

data APIKeyDisable

-- | @application/json@
instance Consumes APIKeyDisable MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes APIKeyDisable MimeFormUrlEncoded

-- | @application/json@
instance Produces APIKeyDisable MimeJSON
-- | @application/xml@
instance Produces APIKeyDisable MimeXML
-- | @text/xml@
instance Produces APIKeyDisable MimeTextxml
-- | @application/javascript@
instance Produces APIKeyDisable MimeJavascript
-- | @text/javascript@
instance Produces APIKeyDisable MimeTextjavascript


-- *** aPIKeyEnable

-- | @POST \/apiKey\/enable@
-- 
-- Enable an API Key.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
aPIKeyEnable
  :: (Consumes APIKeyEnable contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> ApiKeyId -- ^ "apiKeyId" -  API Key ID (public component).
  -> BitMEXRequest APIKeyEnable contentType APIKey accept
aPIKeyEnable _  _ (ApiKeyId apiKeyId) =
  _mkRequest "POST" ["/apiKey/enable"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("apiKeyID", apiKeyId)

data APIKeyEnable

-- | @application/json@
instance Consumes APIKeyEnable MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes APIKeyEnable MimeFormUrlEncoded

-- | @application/json@
instance Produces APIKeyEnable MimeJSON
-- | @application/xml@
instance Produces APIKeyEnable MimeXML
-- | @text/xml@
instance Produces APIKeyEnable MimeTextxml
-- | @application/javascript@
instance Produces APIKeyEnable MimeJavascript
-- | @text/javascript@
instance Produces APIKeyEnable MimeTextjavascript


-- *** aPIKeyGet

-- | @GET \/apiKey@
-- 
-- Get your API Keys.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
aPIKeyGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest APIKeyGet MimeNoContent [APIKey] accept
aPIKeyGet  _ =
  _mkRequest "GET" ["/apiKey"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data APIKeyGet

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam APIKeyGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | @application/json@
instance Consumes APIKeyGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes APIKeyGet MimeFormUrlEncoded

-- | @application/json@
instance Produces APIKeyGet MimeJSON
-- | @application/xml@
instance Produces APIKeyGet MimeXML
-- | @text/xml@
instance Produces APIKeyGet MimeTextxml
-- | @application/javascript@
instance Produces APIKeyGet MimeJavascript
-- | @text/javascript@
instance Produces APIKeyGet MimeTextjavascript


-- *** aPIKeyNew

-- | @POST \/apiKey@
-- 
-- Create a new API Key.
-- 
-- API Keys can also be created via [this Python script](https://github.com/BitMEX/market-maker/blob/master/generate-api-key.py) See the [API Key Documentation](/app/apiKeys) for more information on capabilities.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
aPIKeyNew
  :: (Consumes APIKeyNew contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest APIKeyNew contentType APIKey accept
aPIKeyNew _  _ =
  _mkRequest "POST" ["/apiKey"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data APIKeyNew

-- | /Optional Param/ "name" - Key name. This name is for reference only.
instance HasOptionalParam APIKeyNew Name where
  applyOptionalParam req (Name xs) =
    req `addForm` toForm ("name", xs)

-- | /Optional Param/ "cidr" - CIDR block to restrict this key to. To restrict to a single address, append \"/32\", e.g. 207.39.29.22/32. Leave blank or set to 0.0.0.0/0 to allow all IPs. Only one block may be set. <a href=\"http://software77.net/cidr-101.html\">More on CIDR blocks</a>
instance HasOptionalParam APIKeyNew Cidr where
  applyOptionalParam req (Cidr xs) =
    req `addForm` toForm ("cidr", xs)

-- | /Optional Param/ "permissions" - Key Permissions. All keys can read margin and position data. Additional permissions must be added. Available: [\"order\", \"orderCancel\", \"withdraw\"].
instance HasOptionalParam APIKeyNew Permissions where
  applyOptionalParam req (Permissions xs) =
    req `addForm` toForm ("permissions", xs)

-- | /Optional Param/ "enabled" - Set to true to enable this key on creation. Otherwise, it must be explicitly enabled via /apiKey/enable.
instance HasOptionalParam APIKeyNew Enabled where
  applyOptionalParam req (Enabled xs) =
    req `addForm` toForm ("enabled", xs)

-- | /Optional Param/ "token" - OTP Token (YubiKey, Google Authenticator)
instance HasOptionalParam APIKeyNew Token where
  applyOptionalParam req (Token xs) =
    req `addForm` toForm ("token", xs)

-- | @application/json@
instance Consumes APIKeyNew MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes APIKeyNew MimeFormUrlEncoded

-- | @application/json@
instance Produces APIKeyNew MimeJSON
-- | @application/xml@
instance Produces APIKeyNew MimeXML
-- | @text/xml@
instance Produces APIKeyNew MimeTextxml
-- | @application/javascript@
instance Produces APIKeyNew MimeJavascript
-- | @text/javascript@
instance Produces APIKeyNew MimeTextjavascript


-- *** aPIKeyRemove

-- | @DELETE \/apiKey@
-- 
-- Remove an API Key.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
aPIKeyRemove
  :: (Consumes APIKeyRemove contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> ApiKeyId -- ^ "apiKeyId" -  API Key ID (public component).
  -> BitMEXRequest APIKeyRemove contentType InlineResponse200 accept
aPIKeyRemove _  _ (ApiKeyId apiKeyId) =
  _mkRequest "DELETE" ["/apiKey"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("apiKeyID", apiKeyId)

data APIKeyRemove

-- | @application/json@
instance Consumes APIKeyRemove MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes APIKeyRemove MimeFormUrlEncoded

-- | @application/json@
instance Produces APIKeyRemove MimeJSON
-- | @application/xml@
instance Produces APIKeyRemove MimeXML
-- | @text/xml@
instance Produces APIKeyRemove MimeTextxml
-- | @application/javascript@
instance Produces APIKeyRemove MimeJavascript
-- | @text/javascript@
instance Produces APIKeyRemove MimeTextjavascript


-- ** Announcement

-- *** announcementGet

-- | @GET \/announcement@
-- 
-- Get site announcements.
-- 
announcementGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest AnnouncementGet MimeNoContent [Announcement] accept
announcementGet  _ =
  _mkRequest "GET" ["/announcement"]

data AnnouncementGet

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.
instance HasOptionalParam AnnouncementGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | @application/json@
instance Consumes AnnouncementGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes AnnouncementGet MimeFormUrlEncoded

-- | @application/json@
instance Produces AnnouncementGet MimeJSON
-- | @application/xml@
instance Produces AnnouncementGet MimeXML
-- | @text/xml@
instance Produces AnnouncementGet MimeTextxml
-- | @application/javascript@
instance Produces AnnouncementGet MimeJavascript
-- | @text/javascript@
instance Produces AnnouncementGet MimeTextjavascript


-- *** announcementGetUrgent

-- | @GET \/announcement\/urgent@
-- 
-- Get urgent (banner) announcements.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
announcementGetUrgent
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest AnnouncementGetUrgent MimeNoContent [Announcement] accept
announcementGetUrgent  _ =
  _mkRequest "GET" ["/announcement/urgent"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data AnnouncementGetUrgent

-- | @application/json@
instance Consumes AnnouncementGetUrgent MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes AnnouncementGetUrgent MimeFormUrlEncoded

-- | @application/json@
instance Produces AnnouncementGetUrgent MimeJSON
-- | @application/xml@
instance Produces AnnouncementGetUrgent MimeXML
-- | @text/xml@
instance Produces AnnouncementGetUrgent MimeTextxml
-- | @application/javascript@
instance Produces AnnouncementGetUrgent MimeJavascript
-- | @text/javascript@
instance Produces AnnouncementGetUrgent MimeTextjavascript


-- ** Chat

-- *** chatGet

-- | @GET \/chat@
-- 
-- Get chat messages.
-- 
chatGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest ChatGet MimeNoContent [Chat] accept
chatGet  _ =
  _mkRequest "GET" ["/chat"]

data ChatGet

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam ChatGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting ID for results.
instance HasOptionalParam ChatGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam ChatGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "channelID" - Channel id. GET /chat/channels for ids. Leave blank for all.
instance HasOptionalParam ChatGet ChannelId where
  applyOptionalParam req (ChannelId xs) =
    req `setQuery` toQuery ("channelID", Just xs)

-- | @application/json@
instance Consumes ChatGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes ChatGet MimeFormUrlEncoded

-- | @application/json@
instance Produces ChatGet MimeJSON
-- | @application/xml@
instance Produces ChatGet MimeXML
-- | @text/xml@
instance Produces ChatGet MimeTextxml
-- | @application/javascript@
instance Produces ChatGet MimeJavascript
-- | @text/javascript@
instance Produces ChatGet MimeTextjavascript


-- *** chatGetChannels

-- | @GET \/chat\/channels@
-- 
-- Get available channels.
-- 
chatGetChannels
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest ChatGetChannels MimeNoContent [ChatChannels] accept
chatGetChannels  _ =
  _mkRequest "GET" ["/chat/channels"]

data ChatGetChannels

-- | @application/json@
instance Consumes ChatGetChannels MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes ChatGetChannels MimeFormUrlEncoded

-- | @application/json@
instance Produces ChatGetChannels MimeJSON
-- | @application/xml@
instance Produces ChatGetChannels MimeXML
-- | @text/xml@
instance Produces ChatGetChannels MimeTextxml
-- | @application/javascript@
instance Produces ChatGetChannels MimeJavascript
-- | @text/javascript@
instance Produces ChatGetChannels MimeTextjavascript


-- *** chatGetConnected

-- | @GET \/chat\/connected@
-- 
-- Get connected users.
-- 
-- Returns an array with browser users in the first position and API users (bots) in the second position.
-- 
chatGetConnected
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest ChatGetConnected MimeNoContent ConnectedUsers accept
chatGetConnected  _ =
  _mkRequest "GET" ["/chat/connected"]

data ChatGetConnected

-- | @application/json@
instance Consumes ChatGetConnected MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes ChatGetConnected MimeFormUrlEncoded

-- | @application/json@
instance Produces ChatGetConnected MimeJSON
-- | @application/xml@
instance Produces ChatGetConnected MimeXML
-- | @text/xml@
instance Produces ChatGetConnected MimeTextxml
-- | @application/javascript@
instance Produces ChatGetConnected MimeJavascript
-- | @text/javascript@
instance Produces ChatGetConnected MimeTextjavascript


-- *** chatNew

-- | @POST \/chat@
-- 
-- Send a chat message.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
chatNew
  :: (Consumes ChatNew contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Message -- ^ "message"
  -> BitMEXRequest ChatNew contentType Chat accept
chatNew _  _ (Message message) =
  _mkRequest "POST" ["/chat"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("message", message)

data ChatNew

-- | /Optional Param/ "channelID" - Channel to post to. Default 1 (English).
instance HasOptionalParam ChatNew ChannelId where
  applyOptionalParam req (ChannelId xs) =
    req `addForm` toForm ("channelID", xs)

-- | @application/json@
instance Consumes ChatNew MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes ChatNew MimeFormUrlEncoded

-- | @application/json@
instance Produces ChatNew MimeJSON
-- | @application/xml@
instance Produces ChatNew MimeXML
-- | @text/xml@
instance Produces ChatNew MimeTextxml
-- | @application/javascript@
instance Produces ChatNew MimeJavascript
-- | @text/javascript@
instance Produces ChatNew MimeTextjavascript


-- ** Execution

-- *** executionGet

-- | @GET \/execution@
-- 
-- Get all raw executions for your account.
-- 
-- This returns all raw transactions, which includes order opening and cancelation, and order status changes. It can be quite noisy. More focused information is available at `/execution/tradeHistory`.  You may also use the `filter` param to target your query. Specify an array as a filter value, such as `{\"execType\": [\"Settlement\", \"Trade\"]}` to filter on multiple values.  See [the FIX Spec](http://www.onixs.biz/fix-dictionary/5.0.SP2/msgType_8_8.html) for explanations of these fields. 
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
executionGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest ExecutionGet MimeNoContent [Execution] accept
executionGet  _ =
  _mkRequest "GET" ["/execution"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data ExecutionGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam ExecutionGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam ExecutionGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam ExecutionGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam ExecutionGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam ExecutionGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam ExecutionGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam ExecutionGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam ExecutionGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes ExecutionGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes ExecutionGet MimeFormUrlEncoded

-- | @application/json@
instance Produces ExecutionGet MimeJSON
-- | @application/xml@
instance Produces ExecutionGet MimeXML
-- | @text/xml@
instance Produces ExecutionGet MimeTextxml
-- | @application/javascript@
instance Produces ExecutionGet MimeJavascript
-- | @text/javascript@
instance Produces ExecutionGet MimeTextjavascript


-- *** executionGetTradeHistory

-- | @GET \/execution\/tradeHistory@
-- 
-- Get all balance-affecting executions. This includes each trade, insurance charge, and settlement.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
executionGetTradeHistory
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest ExecutionGetTradeHistory MimeNoContent [Execution] accept
executionGetTradeHistory  _ =
  _mkRequest "GET" ["/execution/tradeHistory"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data ExecutionGetTradeHistory

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam ExecutionGetTradeHistory Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam ExecutionGetTradeHistory Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam ExecutionGetTradeHistory Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam ExecutionGetTradeHistory Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam ExecutionGetTradeHistory Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam ExecutionGetTradeHistory Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam ExecutionGetTradeHistory StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam ExecutionGetTradeHistory EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes ExecutionGetTradeHistory MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes ExecutionGetTradeHistory MimeFormUrlEncoded

-- | @application/json@
instance Produces ExecutionGetTradeHistory MimeJSON
-- | @application/xml@
instance Produces ExecutionGetTradeHistory MimeXML
-- | @text/xml@
instance Produces ExecutionGetTradeHistory MimeTextxml
-- | @application/javascript@
instance Produces ExecutionGetTradeHistory MimeJavascript
-- | @text/javascript@
instance Produces ExecutionGetTradeHistory MimeTextjavascript


-- ** Funding

-- *** fundingGet

-- | @GET \/funding@
-- 
-- Get funding history.
-- 
fundingGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest FundingGet MimeNoContent [Funding] accept
fundingGet  _ =
  _mkRequest "GET" ["/funding"]

data FundingGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam FundingGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam FundingGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam FundingGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam FundingGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam FundingGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam FundingGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam FundingGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam FundingGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes FundingGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes FundingGet MimeFormUrlEncoded

-- | @application/json@
instance Produces FundingGet MimeJSON
-- | @application/xml@
instance Produces FundingGet MimeXML
-- | @text/xml@
instance Produces FundingGet MimeTextxml
-- | @application/javascript@
instance Produces FundingGet MimeJavascript
-- | @text/javascript@
instance Produces FundingGet MimeTextjavascript


-- ** Instrument

-- *** instrumentGet

-- | @GET \/instrument@
-- 
-- Get instruments.
-- 
-- This returns all instruments and indices, including those that have settled or are unlisted. Use this endpoint if you want to query for individual instruments or use a complex filter. Use `/instrument/active` to return active instruments, or use a filter like `{\"state\": \"Open\"}`.
-- 
instrumentGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest InstrumentGet MimeNoContent [Instrument] accept
instrumentGet  _ =
  _mkRequest "GET" ["/instrument"]

data InstrumentGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam InstrumentGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam InstrumentGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam InstrumentGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam InstrumentGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam InstrumentGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam InstrumentGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam InstrumentGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam InstrumentGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes InstrumentGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes InstrumentGet MimeFormUrlEncoded

-- | @application/json@
instance Produces InstrumentGet MimeJSON
-- | @application/xml@
instance Produces InstrumentGet MimeXML
-- | @text/xml@
instance Produces InstrumentGet MimeTextxml
-- | @application/javascript@
instance Produces InstrumentGet MimeJavascript
-- | @text/javascript@
instance Produces InstrumentGet MimeTextjavascript


-- *** instrumentGetActive

-- | @GET \/instrument\/active@
-- 
-- Get all active instruments and instruments that have expired in <24hrs.
-- 
instrumentGetActive
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest InstrumentGetActive MimeNoContent [Instrument] accept
instrumentGetActive  _ =
  _mkRequest "GET" ["/instrument/active"]

data InstrumentGetActive

-- | @application/json@
instance Consumes InstrumentGetActive MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes InstrumentGetActive MimeFormUrlEncoded

-- | @application/json@
instance Produces InstrumentGetActive MimeJSON
-- | @application/xml@
instance Produces InstrumentGetActive MimeXML
-- | @text/xml@
instance Produces InstrumentGetActive MimeTextxml
-- | @application/javascript@
instance Produces InstrumentGetActive MimeJavascript
-- | @text/javascript@
instance Produces InstrumentGetActive MimeTextjavascript


-- *** instrumentGetActiveAndIndices

-- | @GET \/instrument\/activeAndIndices@
-- 
-- Helper method. Gets all active instruments and all indices. This is a join of the result of /indices and /active.
-- 
instrumentGetActiveAndIndices
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest InstrumentGetActiveAndIndices MimeNoContent [Instrument] accept
instrumentGetActiveAndIndices  _ =
  _mkRequest "GET" ["/instrument/activeAndIndices"]

data InstrumentGetActiveAndIndices

-- | @application/json@
instance Consumes InstrumentGetActiveAndIndices MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes InstrumentGetActiveAndIndices MimeFormUrlEncoded

-- | @application/json@
instance Produces InstrumentGetActiveAndIndices MimeJSON
-- | @application/xml@
instance Produces InstrumentGetActiveAndIndices MimeXML
-- | @text/xml@
instance Produces InstrumentGetActiveAndIndices MimeTextxml
-- | @application/javascript@
instance Produces InstrumentGetActiveAndIndices MimeJavascript
-- | @text/javascript@
instance Produces InstrumentGetActiveAndIndices MimeTextjavascript


-- *** instrumentGetActiveIntervals

-- | @GET \/instrument\/activeIntervals@
-- 
-- Return all active contract series and interval pairs.
-- 
-- This endpoint is useful for determining which pairs are live. It returns two arrays of   strings. The first is intervals, such as `[\"BVOL:daily\", \"BVOL:weekly\", \"XBU:daily\", \"XBU:monthly\", ...]`. These identifiers are usable in any query's `symbol` param. The second array is the current resolution of these intervals. Results are mapped at the same index.
-- 
instrumentGetActiveIntervals
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest InstrumentGetActiveIntervals MimeNoContent InstrumentInterval accept
instrumentGetActiveIntervals  _ =
  _mkRequest "GET" ["/instrument/activeIntervals"]

data InstrumentGetActiveIntervals

-- | @application/json@
instance Consumes InstrumentGetActiveIntervals MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes InstrumentGetActiveIntervals MimeFormUrlEncoded

-- | @application/json@
instance Produces InstrumentGetActiveIntervals MimeJSON
-- | @application/xml@
instance Produces InstrumentGetActiveIntervals MimeXML
-- | @text/xml@
instance Produces InstrumentGetActiveIntervals MimeTextxml
-- | @application/javascript@
instance Produces InstrumentGetActiveIntervals MimeJavascript
-- | @text/javascript@
instance Produces InstrumentGetActiveIntervals MimeTextjavascript


-- *** instrumentGetCompositeIndex

-- | @GET \/instrument\/compositeIndex@
-- 
-- Show constituent parts of an index.
-- 
-- Composite indices are built from multiple external price sources.  Use this endpoint to get the underlying prices of an index. For example, send a `symbol` of `.XBT` to get the ticks and weights of the constituent exchanges that build the \".XBT\" index.  A tick with reference `\"BMI\"` and weight `null` is the composite index tick. 
-- 
instrumentGetCompositeIndex
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest InstrumentGetCompositeIndex MimeNoContent [IndexComposite] accept
instrumentGetCompositeIndex  _ =
  _mkRequest "GET" ["/instrument/compositeIndex"]

data InstrumentGetCompositeIndex
instance HasOptionalParam InstrumentGetCompositeIndex Account where
  applyOptionalParam req (Account xs) =
    req `setQuery` toQuery ("account", Just xs)

-- | /Optional Param/ "symbol" - The composite index symbol.
instance HasOptionalParam InstrumentGetCompositeIndex Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam InstrumentGetCompositeIndex Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam InstrumentGetCompositeIndex Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam InstrumentGetCompositeIndex Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam InstrumentGetCompositeIndex Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam InstrumentGetCompositeIndex Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam InstrumentGetCompositeIndex StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam InstrumentGetCompositeIndex EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes InstrumentGetCompositeIndex MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes InstrumentGetCompositeIndex MimeFormUrlEncoded

-- | @application/json@
instance Produces InstrumentGetCompositeIndex MimeJSON
-- | @application/xml@
instance Produces InstrumentGetCompositeIndex MimeXML
-- | @text/xml@
instance Produces InstrumentGetCompositeIndex MimeTextxml
-- | @application/javascript@
instance Produces InstrumentGetCompositeIndex MimeJavascript
-- | @text/javascript@
instance Produces InstrumentGetCompositeIndex MimeTextjavascript


-- *** instrumentGetIndices

-- | @GET \/instrument\/indices@
-- 
-- Get all price indices.
-- 
instrumentGetIndices
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest InstrumentGetIndices MimeNoContent [Instrument] accept
instrumentGetIndices  _ =
  _mkRequest "GET" ["/instrument/indices"]

data InstrumentGetIndices

-- | @application/json@
instance Consumes InstrumentGetIndices MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes InstrumentGetIndices MimeFormUrlEncoded

-- | @application/json@
instance Produces InstrumentGetIndices MimeJSON
-- | @application/xml@
instance Produces InstrumentGetIndices MimeXML
-- | @text/xml@
instance Produces InstrumentGetIndices MimeTextxml
-- | @application/javascript@
instance Produces InstrumentGetIndices MimeJavascript
-- | @text/javascript@
instance Produces InstrumentGetIndices MimeTextjavascript


-- ** Insurance

-- *** insuranceGet

-- | @GET \/insurance@
-- 
-- Get insurance fund history.
-- 
insuranceGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest InsuranceGet MimeNoContent [Insurance] accept
insuranceGet  _ =
  _mkRequest "GET" ["/insurance"]

data InsuranceGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam InsuranceGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam InsuranceGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam InsuranceGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam InsuranceGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam InsuranceGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam InsuranceGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam InsuranceGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam InsuranceGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes InsuranceGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes InsuranceGet MimeFormUrlEncoded

-- | @application/json@
instance Produces InsuranceGet MimeJSON
-- | @application/xml@
instance Produces InsuranceGet MimeXML
-- | @text/xml@
instance Produces InsuranceGet MimeTextxml
-- | @application/javascript@
instance Produces InsuranceGet MimeJavascript
-- | @text/javascript@
instance Produces InsuranceGet MimeTextjavascript


-- ** Leaderboard

-- *** leaderboardGet

-- | @GET \/leaderboard@
-- 
-- Get current leaderboard.
-- 
leaderboardGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest LeaderboardGet MimeNoContent [Leaderboard] accept
leaderboardGet  _ =
  _mkRequest "GET" ["/leaderboard"]

data LeaderboardGet

-- | /Optional Param/ "method" - Ranking type. Options: \"notional\", \"ROE\"
instance HasOptionalParam LeaderboardGet Method where
  applyOptionalParam req (Method xs) =
    req `setQuery` toQuery ("method", Just xs)

-- | @application/json@
instance Consumes LeaderboardGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes LeaderboardGet MimeFormUrlEncoded

-- | @application/json@
instance Produces LeaderboardGet MimeJSON
-- | @application/xml@
instance Produces LeaderboardGet MimeXML
-- | @text/xml@
instance Produces LeaderboardGet MimeTextxml
-- | @application/javascript@
instance Produces LeaderboardGet MimeJavascript
-- | @text/javascript@
instance Produces LeaderboardGet MimeTextjavascript


-- ** Liquidation

-- *** liquidationGet

-- | @GET \/liquidation@
-- 
-- Get liquidation orders.
-- 
liquidationGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest LiquidationGet MimeNoContent [Liquidation] accept
liquidationGet  _ =
  _mkRequest "GET" ["/liquidation"]

data LiquidationGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam LiquidationGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam LiquidationGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam LiquidationGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam LiquidationGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam LiquidationGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam LiquidationGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam LiquidationGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam LiquidationGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes LiquidationGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes LiquidationGet MimeFormUrlEncoded

-- | @application/json@
instance Produces LiquidationGet MimeJSON
-- | @application/xml@
instance Produces LiquidationGet MimeXML
-- | @text/xml@
instance Produces LiquidationGet MimeTextxml
-- | @application/javascript@
instance Produces LiquidationGet MimeJavascript
-- | @text/javascript@
instance Produces LiquidationGet MimeTextjavascript


-- ** Notification

-- *** notificationGet

-- | @GET \/notification@
-- 
-- Get your current notifications.
-- 
-- This is an upcoming feature and currently does not return data.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
notificationGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest NotificationGet MimeNoContent [Notification] accept
notificationGet  _ =
  _mkRequest "GET" ["/notification"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data NotificationGet

-- | @application/json@
instance Consumes NotificationGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes NotificationGet MimeFormUrlEncoded

-- | @application/json@
instance Produces NotificationGet MimeJSON
-- | @application/xml@
instance Produces NotificationGet MimeXML
-- | @text/xml@
instance Produces NotificationGet MimeTextxml
-- | @application/javascript@
instance Produces NotificationGet MimeJavascript
-- | @text/javascript@
instance Produces NotificationGet MimeTextjavascript


-- ** Order

-- *** orderAmend

-- | @PUT \/order@
-- 
-- Amend the quantity or price of an open order.
-- 
-- Send an `orderID` or `origClOrdID` to identify the order you wish to amend.  Both order quantity and price can be amended. Only one `qty` field can be used to amend.  Use the `leavesQty` field to specify how much of the order you wish to remain open. This can be useful if you want to adjust your position's delta by a certain amount, regardless of how much of the order has already filled.  Use the `simpleOrderQty` and `simpleLeavesQty` fields to specify order size in Bitcoin, rather than contracts. These fields will round up to the nearest contract.  Like order placement, amending can be done in bulk. Simply send a request to `PUT /api/v1/order/bulk` with a JSON body of the shape: `{\"orders\": [{...}, {...}]}`, each object containing the fields used in this endpoint. 
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderAmend
  :: (Consumes OrderAmend contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest OrderAmend contentType Order accept
orderAmend _  _ =
  _mkRequest "PUT" ["/order"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data OrderAmend

-- | /Optional Param/ "orderID" - Order ID
instance HasOptionalParam OrderAmend OrderId where
  applyOptionalParam req (OrderId xs) =
    req `addForm` toForm ("orderID", xs)

-- | /Optional Param/ "origClOrdID" - Client Order ID. See POST /order.
instance HasOptionalParam OrderAmend OrigClOrdId where
  applyOptionalParam req (OrigClOrdId xs) =
    req `addForm` toForm ("origClOrdID", xs)

-- | /Optional Param/ "clOrdID" - Optional new Client Order ID, requires `origClOrdID`.
instance HasOptionalParam OrderAmend ClOrdId where
  applyOptionalParam req (ClOrdId xs) =
    req `addForm` toForm ("clOrdID", xs)

-- | /Optional Param/ "simpleOrderQty" - Optional order quantity in units of the underlying instrument (i.e. Bitcoin).
instance HasOptionalParam OrderAmend SimpleOrderQty where
  applyOptionalParam req (SimpleOrderQty xs) =
    req `addForm` toForm ("simpleOrderQty", xs)

-- | /Optional Param/ "orderQty" - Optional order quantity in units of the instrument (i.e. contracts).
instance HasOptionalParam OrderAmend OrderQty where
  applyOptionalParam req (OrderQty xs) =
    req `addForm` toForm ("orderQty", xs)

-- | /Optional Param/ "simpleLeavesQty" - Optional leaves quantity in units of the underlying instrument (i.e. Bitcoin). Useful for amending partially filled orders.
instance HasOptionalParam OrderAmend SimpleLeavesQty where
  applyOptionalParam req (SimpleLeavesQty xs) =
    req `addForm` toForm ("simpleLeavesQty", xs)

-- | /Optional Param/ "leavesQty" - Optional leaves quantity in units of the instrument (i.e. contracts). Useful for amending partially filled orders.
instance HasOptionalParam OrderAmend LeavesQty where
  applyOptionalParam req (LeavesQty xs) =
    req `addForm` toForm ("leavesQty", xs)

-- | /Optional Param/ "price" - Optional limit price for 'Limit', 'StopLimit', and 'LimitIfTouched' orders.
instance HasOptionalParam OrderAmend Price where
  applyOptionalParam req (Price xs) =
    req `addForm` toForm ("price", xs)

-- | /Optional Param/ "stopPx" - Optional trigger price for 'Stop', 'StopLimit', 'MarketIfTouched', and 'LimitIfTouched' orders. Use a price below the current price for stop-sell orders and buy-if-touched orders.
instance HasOptionalParam OrderAmend StopPx where
  applyOptionalParam req (StopPx xs) =
    req `addForm` toForm ("stopPx", xs)

-- | /Optional Param/ "pegOffsetValue" - Optional trailing offset from the current price for 'Stop', 'StopLimit', 'MarketIfTouched', and 'LimitIfTouched' orders; use a negative offset for stop-sell orders and buy-if-touched orders. Optional offset from the peg price for 'Pegged' orders.
instance HasOptionalParam OrderAmend PegOffsetValue where
  applyOptionalParam req (PegOffsetValue xs) =
    req `addForm` toForm ("pegOffsetValue", xs)

-- | /Optional Param/ "text" - Optional amend annotation. e.g. 'Adjust skew'.
instance HasOptionalParam OrderAmend ParamText where
  applyOptionalParam req (ParamText xs) =
    req `addForm` toForm ("text", xs)

-- | @application/json@
instance Consumes OrderAmend MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderAmend MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderAmend MimeJSON
-- | @application/xml@
instance Produces OrderAmend MimeXML
-- | @text/xml@
instance Produces OrderAmend MimeTextxml
-- | @application/javascript@
instance Produces OrderAmend MimeJavascript
-- | @text/javascript@
instance Produces OrderAmend MimeTextjavascript


-- *** orderAmendBulk

-- | @PUT \/order\/bulk@
-- 
-- Amend multiple orders for the same symbol.
-- 
-- Similar to POST /amend, but with multiple orders. `application/json` only. Ratelimited at 50%.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderAmendBulk
  :: (Consumes OrderAmendBulk contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest OrderAmendBulk contentType [Order] accept
orderAmendBulk _  _ =
  _mkRequest "PUT" ["/order/bulk"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data OrderAmendBulk

-- | /Optional Param/ "orders" - An array of orders.
instance HasOptionalParam OrderAmendBulk Orders where
  applyOptionalParam req (Orders xs) =
    req `addForm` toForm ("orders", xs)

-- | @application/json@
instance Consumes OrderAmendBulk MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderAmendBulk MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderAmendBulk MimeJSON
-- | @application/xml@
instance Produces OrderAmendBulk MimeXML
-- | @text/xml@
instance Produces OrderAmendBulk MimeTextxml
-- | @application/javascript@
instance Produces OrderAmendBulk MimeJavascript
-- | @text/javascript@
instance Produces OrderAmendBulk MimeTextjavascript


-- *** orderCancel

-- | @DELETE \/order@
-- 
-- Cancel order(s). Send multiple order IDs to cancel in bulk.
-- 
-- Either an orderID or a clOrdID must be provided.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderCancel
  :: (Consumes OrderCancel contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest OrderCancel contentType [Order] accept
orderCancel _  _ =
  _mkRequest "DELETE" ["/order"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data OrderCancel

-- | /Optional Param/ "orderID" - Order ID(s).
instance HasOptionalParam OrderCancel OrderId where
  applyOptionalParam req (OrderId xs) =
    req `addForm` toForm ("orderID", xs)

-- | /Optional Param/ "clOrdID" - Client Order ID(s). See POST /order.
instance HasOptionalParam OrderCancel ClOrdId where
  applyOptionalParam req (ClOrdId xs) =
    req `addForm` toForm ("clOrdID", xs)

-- | /Optional Param/ "text" - Optional cancellation annotation. e.g. 'Spread Exceeded'.
instance HasOptionalParam OrderCancel ParamText where
  applyOptionalParam req (ParamText xs) =
    req `addForm` toForm ("text", xs)

-- | @application/json@
instance Consumes OrderCancel MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderCancel MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderCancel MimeJSON
-- | @application/xml@
instance Produces OrderCancel MimeXML
-- | @text/xml@
instance Produces OrderCancel MimeTextxml
-- | @application/javascript@
instance Produces OrderCancel MimeJavascript
-- | @text/javascript@
instance Produces OrderCancel MimeTextjavascript


-- *** orderCancelAll

-- | @DELETE \/order\/all@
-- 
-- Cancels all of your orders.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderCancelAll
  :: (Consumes OrderCancelAll contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest OrderCancelAll contentType A.Value accept
orderCancelAll _  _ =
  _mkRequest "DELETE" ["/order/all"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data OrderCancelAll

-- | /Optional Param/ "symbol" - Optional symbol. If provided, only cancels orders for that symbol.
instance HasOptionalParam OrderCancelAll Symbol where
  applyOptionalParam req (Symbol xs) =
    req `addForm` toForm ("symbol", xs)

-- | /Optional Param/ "filter" - Optional filter for cancellation. Use to only cancel some orders, e.g. `{\"side\": \"Buy\"}`.
instance HasOptionalParam OrderCancelAll Filter where
  applyOptionalParam req (Filter xs) =
    req `addForm` toForm ("filter", xs)

-- | /Optional Param/ "text" - Optional cancellation annotation. e.g. 'Spread Exceeded'
instance HasOptionalParam OrderCancelAll ParamText where
  applyOptionalParam req (ParamText xs) =
    req `addForm` toForm ("text", xs)

-- | @application/json@
instance Consumes OrderCancelAll MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderCancelAll MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderCancelAll MimeJSON
-- | @application/xml@
instance Produces OrderCancelAll MimeXML
-- | @text/xml@
instance Produces OrderCancelAll MimeTextxml
-- | @application/javascript@
instance Produces OrderCancelAll MimeJavascript
-- | @text/javascript@
instance Produces OrderCancelAll MimeTextjavascript


-- *** orderCancelAllAfter

-- | @POST \/order\/cancelAllAfter@
-- 
-- Automatically cancel all your orders after a specified timeout.
-- 
-- Useful as a dead-man's switch to ensure your orders are canceled in case of an outage. If called repeatedly, the existing offset will be canceled and a new one will be inserted in its place.  Example usage: call this route at 15s intervals with an offset of 60000 (60s). If this route is not called within 60 seconds, all your orders will be automatically canceled.  This is also available via [WebSocket](https://www.bitmex.com/app/wsAPI#dead-man-s-switch-auto-cancel-). 
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderCancelAllAfter
  :: (Consumes OrderCancelAllAfter contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Timeout -- ^ "timeout" -  Timeout in ms. Set to 0 to cancel this timer. 
  -> BitMEXRequest OrderCancelAllAfter contentType A.Value accept
orderCancelAllAfter _  _ (Timeout timeout) =
  _mkRequest "POST" ["/order/cancelAllAfter"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("timeout", timeout)

data OrderCancelAllAfter

-- | @application/json@
instance Consumes OrderCancelAllAfter MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderCancelAllAfter MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderCancelAllAfter MimeJSON
-- | @application/xml@
instance Produces OrderCancelAllAfter MimeXML
-- | @text/xml@
instance Produces OrderCancelAllAfter MimeTextxml
-- | @application/javascript@
instance Produces OrderCancelAllAfter MimeJavascript
-- | @text/javascript@
instance Produces OrderCancelAllAfter MimeTextjavascript


-- *** orderClosePosition

-- | @POST \/order\/closePosition@
-- 
-- Close a position. [Deprecated, use POST /order with execInst: 'Close']
-- 
-- If no `price` is specified, a market order will be submitted to close the whole of your position. This will also close all other open orders in this symbol.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderClosePosition
  :: (Consumes OrderClosePosition contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Symbol of position to close.
  -> BitMEXRequest OrderClosePosition contentType Order accept
orderClosePosition _  _ (Symbol symbol) =
  _mkRequest "POST" ["/order/closePosition"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("symbol", symbol)

data OrderClosePosition

-- | /Optional Param/ "price" - Optional limit price.
instance HasOptionalParam OrderClosePosition Price where
  applyOptionalParam req (Price xs) =
    req `addForm` toForm ("price", xs)

-- | @application/json@
instance Consumes OrderClosePosition MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderClosePosition MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderClosePosition MimeJSON
-- | @application/xml@
instance Produces OrderClosePosition MimeXML
-- | @text/xml@
instance Produces OrderClosePosition MimeTextxml
-- | @application/javascript@
instance Produces OrderClosePosition MimeJavascript
-- | @text/javascript@
instance Produces OrderClosePosition MimeTextjavascript


-- *** orderGetOrders

-- | @GET \/order@
-- 
-- Get your orders.
-- 
-- To get open orders only, send {\"open\": true} in the filter param.  See <a href=\"http://www.onixs.biz/fix-dictionary/5.0.SP2/msgType_D_68.html\">the FIX Spec</a> for explanations of these fields.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderGetOrders
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest OrderGetOrders MimeNoContent [Order] accept
orderGetOrders  _ =
  _mkRequest "GET" ["/order"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data OrderGetOrders

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam OrderGetOrders Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam OrderGetOrders Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam OrderGetOrders Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam OrderGetOrders Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam OrderGetOrders Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam OrderGetOrders Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam OrderGetOrders StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam OrderGetOrders EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes OrderGetOrders MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderGetOrders MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderGetOrders MimeJSON
-- | @application/xml@
instance Produces OrderGetOrders MimeXML
-- | @text/xml@
instance Produces OrderGetOrders MimeTextxml
-- | @application/javascript@
instance Produces OrderGetOrders MimeJavascript
-- | @text/javascript@
instance Produces OrderGetOrders MimeTextjavascript


-- *** orderNew

-- | @POST \/order@
-- 
-- Create a new order.
-- 
-- ## Placing Orders  This endpoint is used for placing orders. See individual fields below for more details on their use.  #### Order Types  All orders require a `symbol`. All other fields are optional except when otherwise specified.  These are the valid `ordType`s:  * **Limit**: The default order type. Specify an `orderQty` and `price`. * **Market**: A traditional Market order. A Market order will execute until filled or your bankruptcy price is reached, at   which point it will cancel. * **MarketWithLeftOverAsLimit**: A market order that, after eating through the order book as far as   permitted by available margin, will become a limit order. The difference between this type and `Market` only   affects the behavior in thin books. Upon reaching the deepest possible price, if there is quantity left over,   a `Market` order will cancel the remaining quantity. `MarketWithLeftOverAsLimit` will keep the remaining   quantity in the books as a `Limit`. * **Stop**: A Stop Market order. Specify an `orderQty` and `stopPx`. When the `stopPx` is reached, the order will be entered   into the book.   * On sell orders, the order will trigger if the triggering price is lower than the `stopPx`. On buys, higher.   * Note: Stop orders do not consume margin until triggered. Be sure that the required margin is available in your     account so that it may trigger fully.   * `Close` Stops don't require an `orderQty`. See Execution Instructions below. * **StopLimit**: Like a Stop Market, but enters a Limit order instead of a Market order. Specify an `orderQty`, `stopPx`,   and `price`. * **MarketIfTouched**: Similar to a Stop, but triggers are done in the opposite direction. Useful for Take Profit orders. * **LimitIfTouched**: As above; use for Take Profit Limit orders.  #### Execution Instructions  The following `execInst`s are supported. If using multiple, separate with a comma (e.g. `LastPrice,Close`).  * **ParticipateDoNotInitiate**: Also known as a Post-Only order. If this order would have executed on placement,   it will cancel instead. * **AllOrNone**: Valid only for hidden orders (`displayQty: 0`). Use to only execute if the entire order would fill. * **MarkPrice, LastPrice, IndexPrice**: Used by stop and if-touched orders to determine the triggering price.   Use only one. By default, `'MarkPrice'` is used. Also used for Pegged orders to define the value of `'LastPeg'`. * **ReduceOnly**: A `'ReduceOnly'` order can only reduce your position, not increase it. If you have a `'ReduceOnly'`   limit order that rests in the order book while the position is reduced by other orders, then its order quantity will   be amended down or canceled. If there are multiple `'ReduceOnly'` orders the least agresssive will be amended first. * **Close**: `'Close'` implies `'ReduceOnly'`. A `'Close'` order will cancel other active limit orders with the same side   and symbol if the open quantity exceeds the current position. This is useful for stops: by canceling these orders, a   `'Close'` Stop is ensured to have the margin required to execute, and can only execute up to the full size of your   position. If not specified, a `'Close'` order has an `orderQty` equal to your current position's size.  #### Linked Orders  Linked Orders are an advanced capability. It is very powerful, but its use requires careful coding and testing. Please follow this document carefully and use the [Testnet Exchange](https://testnet.bitmex.com) while developing.  BitMEX offers four advanced Linked Order types:  * **OCO**: *One Cancels the Other*. A very flexible version of the standard Stop / Take Profit technique.   Multiple orders may be linked together using a single `clOrdLinkID`. Send a `contingencyType` of   `OneCancelsTheOther` on the orders. The first order that fully or partially executes (or activates   for `Stop` orders) will cancel all other orders with the same `clOrdLinkID`. * **OTO**: *One Triggers the Other*. Send a `contingencyType` of `'OneTriggersTheOther'` on the primary order and   then subsequent orders with the same `clOrdLinkID` will be not be triggered until the primary order fully executes. * **OUOA**: *One Updates the Other Absolute*. Send a `contingencyType` of `'OneUpdatesTheOtherAbsolute'` on the orders. Then   as one order has a execution, other orders with the same `clOrdLinkID` will have their order quantity amended   down by the execution quantity. * **OUOP**: *One Updates the Other Proportional*. Send a `contingencyType` of `'OneUpdatesTheOtherProportional'` on the orders. Then   as one order has a execution, other orders with the same `clOrdLinkID` will have their order quantity reduced proportionally   by the fill percentage.  #### Trailing Stops  You may use `pegPriceType` of `'TrailingStopPeg'` to create Trailing Stops. The pegged `stopPx` will move as the market moves away from the peg, and freeze as the market moves toward it.  To use, combine with `pegOffsetValue` to set the `stopPx` of your order. The peg is set to the triggering price specified in the `execInst` (default `'MarkPrice'`). Use a negative offset for stop-sell and buy-if-touched orders.  Requires `ordType`: `'Stop', 'StopLimit', 'MarketIfTouched', 'LimitIfTouched'`.  #### Simple Quantities  Send a `simpleOrderQty` instead of an `orderQty` to create an order denominated in the underlying currency. This is useful for opening up a position with 1 XBT of exposure without having to calculate how many contracts it is.  #### Rate Limits  See the [Bulk Order Documentation](#!/Order/Order_newBulk) if you need to place multiple orders at the same time. Bulk orders require fewer risk checks in the trading engine and thus are ratelimited at **1/10** the normal rate.  You can also improve your reactivity to market movements while staying under your ratelimit by using the [Amend](#!/Order/Order_amend) and [Amend Bulk](#!/Order/Order_amendBulk) endpoints. This allows you to stay in the market and avoids the cancel/replace cycle.  #### Tracking Your Orders  If you want to keep track of order IDs yourself, set a unique `clOrdID` per order. This `clOrdID` will come back as a property on the order and any related executions (including on the WebSocket), and can be used to get or cancel the order. Max length is 36 characters. 
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderNew
  :: (Consumes OrderNew contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Instrument symbol. e.g. 'XBTUSD'.
  -> BitMEXRequest OrderNew contentType Order accept
orderNew _  _ (Symbol symbol) =
  _mkRequest "POST" ["/order"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("symbol", symbol)

data OrderNew

-- | /Optional Param/ "side" - Order side. Valid options: Buy, Sell. Defaults to 'Buy' unless `orderQty` or `simpleOrderQty` is negative.
instance HasOptionalParam OrderNew Side where
  applyOptionalParam req (Side xs) =
    req `addForm` toForm ("side", xs)

-- | /Optional Param/ "simpleOrderQty" - Order quantity in units of the underlying instrument (i.e. Bitcoin).
instance HasOptionalParam OrderNew SimpleOrderQty where
  applyOptionalParam req (SimpleOrderQty xs) =
    req `addForm` toForm ("simpleOrderQty", xs)

-- | /Optional Param/ "quantity" - Deprecated: use `orderQty`.
instance HasOptionalParam OrderNew Quantity where
  applyOptionalParam req (Quantity xs) =
    req `addForm` toForm ("quantity", xs)

-- | /Optional Param/ "orderQty" - Order quantity in units of the instrument (i.e. contracts).
instance HasOptionalParam OrderNew OrderQty where
  applyOptionalParam req (OrderQty xs) =
    req `addForm` toForm ("orderQty", xs)

-- | /Optional Param/ "price" - Optional limit price for 'Limit', 'StopLimit', and 'LimitIfTouched' orders.
instance HasOptionalParam OrderNew Price where
  applyOptionalParam req (Price xs) =
    req `addForm` toForm ("price", xs)

-- | /Optional Param/ "displayQty" - Optional quantity to display in the book. Use 0 for a fully hidden order.
instance HasOptionalParam OrderNew DisplayQty where
  applyOptionalParam req (DisplayQty xs) =
    req `addForm` toForm ("displayQty", xs)

-- | /Optional Param/ "stopPrice" - Deprecated: use `stopPx`.
instance HasOptionalParam OrderNew StopPrice where
  applyOptionalParam req (StopPrice xs) =
    req `addForm` toForm ("stopPrice", xs)

-- | /Optional Param/ "stopPx" - Optional trigger price for 'Stop', 'StopLimit', 'MarketIfTouched', and 'LimitIfTouched' orders. Use a price below the current price for stop-sell orders and buy-if-touched orders. Use `execInst` of 'MarkPrice' or 'LastPrice' to define the current price used for triggering.
instance HasOptionalParam OrderNew StopPx where
  applyOptionalParam req (StopPx xs) =
    req `addForm` toForm ("stopPx", xs)

-- | /Optional Param/ "clOrdID" - Optional Client Order ID. This clOrdID will come back on the order and any related executions.
instance HasOptionalParam OrderNew ClOrdId where
  applyOptionalParam req (ClOrdId xs) =
    req `addForm` toForm ("clOrdID", xs)

-- | /Optional Param/ "clOrdLinkID" - Optional Client Order Link ID for contingent orders.
instance HasOptionalParam OrderNew ClOrdLinkId where
  applyOptionalParam req (ClOrdLinkId xs) =
    req `addForm` toForm ("clOrdLinkID", xs)

-- | /Optional Param/ "pegOffsetValue" - Optional trailing offset from the current price for 'Stop', 'StopLimit', 'MarketIfTouched', and 'LimitIfTouched' orders; use a negative offset for stop-sell orders and buy-if-touched orders. Optional offset from the peg price for 'Pegged' orders.
instance HasOptionalParam OrderNew PegOffsetValue where
  applyOptionalParam req (PegOffsetValue xs) =
    req `addForm` toForm ("pegOffsetValue", xs)

-- | /Optional Param/ "pegPriceType" - Optional peg price type. Valid options: LastPeg, MidPricePeg, MarketPeg, PrimaryPeg, TrailingStopPeg.
instance HasOptionalParam OrderNew PegPriceType where
  applyOptionalParam req (PegPriceType xs) =
    req `addForm` toForm ("pegPriceType", xs)

-- | /Optional Param/ "type" - Deprecated: use `ordType`.
instance HasOptionalParam OrderNew ParamType where
  applyOptionalParam req (ParamType xs) =
    req `addForm` toForm ("type", xs)

-- | /Optional Param/ "ordType" - Order type. Valid options: Market, Limit, Stop, StopLimit, MarketIfTouched, LimitIfTouched, MarketWithLeftOverAsLimit, Pegged. Defaults to 'Limit' when `price` is specified. Defaults to 'Stop' when `stopPx` is specified. Defaults to 'StopLimit' when `price` and `stopPx` are specified.
instance HasOptionalParam OrderNew OrdType where
  applyOptionalParam req (OrdType xs) =
    req `addForm` toForm ("ordType", xs)

-- | /Optional Param/ "timeInForce" - Time in force. Valid options: Day, GoodTillCancel, ImmediateOrCancel, FillOrKill. Defaults to 'GoodTillCancel' for 'Limit', 'StopLimit', 'LimitIfTouched', and 'MarketWithLeftOverAsLimit' orders.
instance HasOptionalParam OrderNew TimeInForce where
  applyOptionalParam req (TimeInForce xs) =
    req `addForm` toForm ("timeInForce", xs)

-- | /Optional Param/ "execInst" - Optional execution instructions. Valid options: ParticipateDoNotInitiate, AllOrNone, MarkPrice, IndexPrice, LastPrice, Close, ReduceOnly, Fixed. 'AllOrNone' instruction requires `displayQty` to be 0. 'MarkPrice', 'IndexPrice' or 'LastPrice' instruction valid for 'Stop', 'StopLimit', 'MarketIfTouched', and 'LimitIfTouched' orders.
instance HasOptionalParam OrderNew ExecInst where
  applyOptionalParam req (ExecInst xs) =
    req `addForm` toForm ("execInst", xs)

-- | /Optional Param/ "contingencyType" - Optional contingency type for use with `clOrdLinkID`. Valid options: OneCancelsTheOther, OneTriggersTheOther, OneUpdatesTheOtherAbsolute, OneUpdatesTheOtherProportional.
instance HasOptionalParam OrderNew ContingencyType where
  applyOptionalParam req (ContingencyType xs) =
    req `addForm` toForm ("contingencyType", xs)

-- | /Optional Param/ "text" - Optional order annotation. e.g. 'Take profit'.
instance HasOptionalParam OrderNew ParamText where
  applyOptionalParam req (ParamText xs) =
    req `addForm` toForm ("text", xs)

-- | @application/json@
instance Consumes OrderNew MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderNew MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderNew MimeJSON
-- | @application/xml@
instance Produces OrderNew MimeXML
-- | @text/xml@
instance Produces OrderNew MimeTextxml
-- | @application/javascript@
instance Produces OrderNew MimeJavascript
-- | @text/javascript@
instance Produces OrderNew MimeTextjavascript


-- *** orderNewBulk

-- | @POST \/order\/bulk@
-- 
-- Create multiple new orders for the same symbol.
-- 
-- This endpoint is used for placing bulk orders. Valid order types are Market, Limit, Stop, StopLimit, MarketIfTouched, LimitIfTouched, MarketWithLeftOverAsLimit, and Pegged.  Each individual order object in the array should have the same properties as an individual POST /order call.  This endpoint is much faster for getting many orders into the book at once. Because it reduces load on BitMEX systems, this endpoint is ratelimited at `ceil(0.1 * orders)`. Submitting 10 orders via a bulk order call will only count as 1 request, 15 as 2, 32 as 4, and so on.  For now, only `application/json` is supported on this endpoint. 
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
orderNewBulk
  :: (Consumes OrderNewBulk contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest OrderNewBulk contentType [Order] accept
orderNewBulk _  _ =
  _mkRequest "POST" ["/order/bulk"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data OrderNewBulk

-- | /Optional Param/ "orders" - An array of orders.
instance HasOptionalParam OrderNewBulk Orders where
  applyOptionalParam req (Orders xs) =
    req `addForm` toForm ("orders", xs)

-- | @application/json@
instance Consumes OrderNewBulk MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderNewBulk MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderNewBulk MimeJSON
-- | @application/xml@
instance Produces OrderNewBulk MimeXML
-- | @text/xml@
instance Produces OrderNewBulk MimeTextxml
-- | @application/javascript@
instance Produces OrderNewBulk MimeJavascript
-- | @text/javascript@
instance Produces OrderNewBulk MimeTextjavascript


-- ** OrderBook

-- *** orderBookGet

-- | @GET \/orderBook@
-- 
-- Get current orderbook [deprecated, use /orderBook/L2].
-- 
orderBookGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Instrument symbol. Send a series (e.g. XBT) to get data for the nearest contract in that series.
  -> BitMEXRequest OrderBookGet MimeNoContent [OrderBook] accept
orderBookGet  _ (Symbol symbol) =
  _mkRequest "GET" ["/orderBook"]
    `setQuery` toQuery ("symbol", Just symbol)

data OrderBookGet

-- | /Optional Param/ "depth" - Orderbook depth.
instance HasOptionalParam OrderBookGet Depth where
  applyOptionalParam req (Depth xs) =
    req `setQuery` toQuery ("depth", Just xs)

-- | @application/json@
instance Consumes OrderBookGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderBookGet MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderBookGet MimeJSON
-- | @application/xml@
instance Produces OrderBookGet MimeXML
-- | @text/xml@
instance Produces OrderBookGet MimeTextxml
-- | @application/javascript@
instance Produces OrderBookGet MimeJavascript
-- | @text/javascript@
instance Produces OrderBookGet MimeTextjavascript


-- *** orderBookGetL2

-- | @GET \/orderBook\/L2@
-- 
-- Get current orderbook in vertical format.
-- 
orderBookGetL2
  :: Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Instrument symbol. Send a series (e.g. XBT) to get data for the nearest contract in that series.
  -> BitMEXRequest OrderBookGetL2 MimeNoContent [OrderBookL2] accept
orderBookGetL2  _ (Symbol symbol) =
  _mkRequest "GET" ["/orderBook/L2"]
    `setQuery` toQuery ("symbol", Just symbol)

data OrderBookGetL2

-- | /Optional Param/ "depth" - Orderbook depth per side. Send 0 for full depth.
instance HasOptionalParam OrderBookGetL2 Depth where
  applyOptionalParam req (Depth xs) =
    req `setQuery` toQuery ("depth", Just xs)

-- | @application/json@
instance Consumes OrderBookGetL2 MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes OrderBookGetL2 MimeFormUrlEncoded

-- | @application/json@
instance Produces OrderBookGetL2 MimeJSON
-- | @application/xml@
instance Produces OrderBookGetL2 MimeXML
-- | @text/xml@
instance Produces OrderBookGetL2 MimeTextxml
-- | @application/javascript@
instance Produces OrderBookGetL2 MimeJavascript
-- | @text/javascript@
instance Produces OrderBookGetL2 MimeTextjavascript


-- ** Position

-- *** positionGet

-- | @GET \/position@
-- 
-- Get your positions.
-- 
-- See <a href=\"http://www.onixs.biz/fix-dictionary/5.0.SP2/msgType_AP_6580.html\">the FIX Spec</a> for explanations of these fields.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
positionGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest PositionGet MimeNoContent [Position] accept
positionGet  _ =
  _mkRequest "GET" ["/position"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data PositionGet

-- | /Optional Param/ "filter" - Table filter. For example, send {\"symbol\": \"XBTUSD\"}.
instance HasOptionalParam PositionGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Which columns to fetch. For example, send [\"columnName\"].
instance HasOptionalParam PositionGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of rows to fetch.
instance HasOptionalParam PositionGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | @application/json@
instance Consumes PositionGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes PositionGet MimeFormUrlEncoded

-- | @application/json@
instance Produces PositionGet MimeJSON
-- | @application/xml@
instance Produces PositionGet MimeXML
-- | @text/xml@
instance Produces PositionGet MimeTextxml
-- | @application/javascript@
instance Produces PositionGet MimeJavascript
-- | @text/javascript@
instance Produces PositionGet MimeTextjavascript


-- *** positionIsolateMargin

-- | @POST \/position\/isolate@
-- 
-- Enable isolated margin or cross margin per-position.
-- 
-- Users can switch isolate margin per-position. This function allows switching margin isolation (aka fixed margin) on and off.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
positionIsolateMargin
  :: (Consumes PositionIsolateMargin contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Position symbol to isolate.
  -> BitMEXRequest PositionIsolateMargin contentType Position accept
positionIsolateMargin _  _ (Symbol symbol) =
  _mkRequest "POST" ["/position/isolate"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("symbol", symbol)

data PositionIsolateMargin

-- | /Optional Param/ "enabled" - True for isolated margin, false for cross margin.
instance HasOptionalParam PositionIsolateMargin Enabled where
  applyOptionalParam req (Enabled xs) =
    req `addForm` toForm ("enabled", xs)

-- | @application/json@
instance Consumes PositionIsolateMargin MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes PositionIsolateMargin MimeFormUrlEncoded

-- | @application/json@
instance Produces PositionIsolateMargin MimeJSON
-- | @application/xml@
instance Produces PositionIsolateMargin MimeXML
-- | @text/xml@
instance Produces PositionIsolateMargin MimeTextxml
-- | @application/javascript@
instance Produces PositionIsolateMargin MimeJavascript
-- | @text/javascript@
instance Produces PositionIsolateMargin MimeTextjavascript


-- *** positionTransferIsolatedMargin

-- | @POST \/position\/transferMargin@
-- 
-- Transfer equity in or out of a position.
-- 
-- When margin is isolated on a position, use this function to add or remove margin from the position. Note that you cannot remove margin below the initial margin threshold.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
positionTransferIsolatedMargin
  :: (Consumes PositionTransferIsolatedMargin contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Symbol of position to isolate.
  -> Amount -- ^ "amount" -  Amount to transfer, in Satoshis. May be negative.
  -> BitMEXRequest PositionTransferIsolatedMargin contentType Position accept
positionTransferIsolatedMargin _  _ (Symbol symbol) (Amount amount) =
  _mkRequest "POST" ["/position/transferMargin"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("symbol", symbol)
    `addForm` toForm ("amount", amount)

data PositionTransferIsolatedMargin

-- | @application/json@
instance Consumes PositionTransferIsolatedMargin MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes PositionTransferIsolatedMargin MimeFormUrlEncoded

-- | @application/json@
instance Produces PositionTransferIsolatedMargin MimeJSON
-- | @application/xml@
instance Produces PositionTransferIsolatedMargin MimeXML
-- | @text/xml@
instance Produces PositionTransferIsolatedMargin MimeTextxml
-- | @application/javascript@
instance Produces PositionTransferIsolatedMargin MimeJavascript
-- | @text/javascript@
instance Produces PositionTransferIsolatedMargin MimeTextjavascript


-- *** positionUpdateLeverage

-- | @POST \/position\/leverage@
-- 
-- Choose leverage for a position.
-- 
-- Users can choose an isolated leverage. This will automatically enable isolated margin.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
positionUpdateLeverage
  :: (Consumes PositionUpdateLeverage contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Symbol of position to adjust.
  -> Leverage -- ^ "leverage" -  Leverage value. Send a number between 0.01 and 100 to enable isolated margin with a fixed leverage. Send 0 to enable cross margin.
  -> BitMEXRequest PositionUpdateLeverage contentType Position accept
positionUpdateLeverage _  _ (Symbol symbol) (Leverage leverage) =
  _mkRequest "POST" ["/position/leverage"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("symbol", symbol)
    `addForm` toForm ("leverage", leverage)

data PositionUpdateLeverage

-- | @application/json@
instance Consumes PositionUpdateLeverage MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes PositionUpdateLeverage MimeFormUrlEncoded

-- | @application/json@
instance Produces PositionUpdateLeverage MimeJSON
-- | @application/xml@
instance Produces PositionUpdateLeverage MimeXML
-- | @text/xml@
instance Produces PositionUpdateLeverage MimeTextxml
-- | @application/javascript@
instance Produces PositionUpdateLeverage MimeJavascript
-- | @text/javascript@
instance Produces PositionUpdateLeverage MimeTextjavascript


-- *** positionUpdateRiskLimit

-- | @POST \/position\/riskLimit@
-- 
-- Update your risk limit.
-- 
-- Risk Limits limit the size of positions you can trade at various margin levels. Larger positions require more margin. Please see the Risk Limit documentation for more details.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
positionUpdateRiskLimit
  :: (Consumes PositionUpdateRiskLimit contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Symbol -- ^ "symbol" -  Symbol of position to isolate.
  -> RiskLimit -- ^ "riskLimit" -  New Risk Limit, in Satoshis.
  -> BitMEXRequest PositionUpdateRiskLimit contentType Position accept
positionUpdateRiskLimit _  _ (Symbol symbol) (RiskLimit riskLimit) =
  _mkRequest "POST" ["/position/riskLimit"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("symbol", symbol)
    `addForm` toForm ("riskLimit", riskLimit)

data PositionUpdateRiskLimit

-- | @application/json@
instance Consumes PositionUpdateRiskLimit MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes PositionUpdateRiskLimit MimeFormUrlEncoded

-- | @application/json@
instance Produces PositionUpdateRiskLimit MimeJSON
-- | @application/xml@
instance Produces PositionUpdateRiskLimit MimeXML
-- | @text/xml@
instance Produces PositionUpdateRiskLimit MimeTextxml
-- | @application/javascript@
instance Produces PositionUpdateRiskLimit MimeJavascript
-- | @text/javascript@
instance Produces PositionUpdateRiskLimit MimeTextjavascript


-- ** Quote

-- *** quoteGet

-- | @GET \/quote@
-- 
-- Get Quotes.
-- 
quoteGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest QuoteGet MimeNoContent [Quote] accept
quoteGet  _ =
  _mkRequest "GET" ["/quote"]

data QuoteGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam QuoteGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam QuoteGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam QuoteGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam QuoteGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam QuoteGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam QuoteGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam QuoteGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam QuoteGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes QuoteGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes QuoteGet MimeFormUrlEncoded

-- | @application/json@
instance Produces QuoteGet MimeJSON
-- | @application/xml@
instance Produces QuoteGet MimeXML
-- | @text/xml@
instance Produces QuoteGet MimeTextxml
-- | @application/javascript@
instance Produces QuoteGet MimeJavascript
-- | @text/javascript@
instance Produces QuoteGet MimeTextjavascript


-- *** quoteGetBucketed

-- | @GET \/quote\/bucketed@
-- 
-- Get previous quotes in time buckets.
-- 
quoteGetBucketed
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest QuoteGetBucketed MimeNoContent [Quote] accept
quoteGetBucketed  _ =
  _mkRequest "GET" ["/quote/bucketed"]

data QuoteGetBucketed

-- | /Optional Param/ "binSize" - Time interval to bucket by. Available options: [1m,5m,1h,1d].
instance HasOptionalParam QuoteGetBucketed BinSize where
  applyOptionalParam req (BinSize xs) =
    req `setQuery` toQuery ("binSize", Just xs)

-- | /Optional Param/ "partial" - If true, will send in-progress (incomplete) bins for the current time period.
instance HasOptionalParam QuoteGetBucketed Partial where
  applyOptionalParam req (Partial xs) =
    req `setQuery` toQuery ("partial", Just xs)

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam QuoteGetBucketed Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam QuoteGetBucketed Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam QuoteGetBucketed Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam QuoteGetBucketed Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam QuoteGetBucketed Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam QuoteGetBucketed Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam QuoteGetBucketed StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam QuoteGetBucketed EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes QuoteGetBucketed MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes QuoteGetBucketed MimeFormUrlEncoded

-- | @application/json@
instance Produces QuoteGetBucketed MimeJSON
-- | @application/xml@
instance Produces QuoteGetBucketed MimeXML
-- | @text/xml@
instance Produces QuoteGetBucketed MimeTextxml
-- | @application/javascript@
instance Produces QuoteGetBucketed MimeJavascript
-- | @text/javascript@
instance Produces QuoteGetBucketed MimeTextjavascript


-- ** Schema

-- *** schemaGet

-- | @GET \/schema@
-- 
-- Get model schemata for data objects returned by this API.
-- 
schemaGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest SchemaGet MimeNoContent A.Value accept
schemaGet  _ =
  _mkRequest "GET" ["/schema"]

data SchemaGet

-- | /Optional Param/ "model" - Optional model filter. If omitted, will return all models.
instance HasOptionalParam SchemaGet Model where
  applyOptionalParam req (Model xs) =
    req `setQuery` toQuery ("model", Just xs)

-- | @application/json@
instance Consumes SchemaGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes SchemaGet MimeFormUrlEncoded

-- | @application/json@
instance Produces SchemaGet MimeJSON
-- | @application/xml@
instance Produces SchemaGet MimeXML
-- | @text/xml@
instance Produces SchemaGet MimeTextxml
-- | @application/javascript@
instance Produces SchemaGet MimeJavascript
-- | @text/javascript@
instance Produces SchemaGet MimeTextjavascript


-- *** schemaWebsocketHelp

-- | @GET \/schema\/websocketHelp@
-- 
-- Returns help text & subject list for websocket usage.
-- 
schemaWebsocketHelp
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest SchemaWebsocketHelp MimeNoContent A.Value accept
schemaWebsocketHelp  _ =
  _mkRequest "GET" ["/schema/websocketHelp"]

data SchemaWebsocketHelp

-- | @application/json@
instance Consumes SchemaWebsocketHelp MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes SchemaWebsocketHelp MimeFormUrlEncoded

-- | @application/json@
instance Produces SchemaWebsocketHelp MimeJSON
-- | @application/xml@
instance Produces SchemaWebsocketHelp MimeXML
-- | @text/xml@
instance Produces SchemaWebsocketHelp MimeTextxml
-- | @application/javascript@
instance Produces SchemaWebsocketHelp MimeJavascript
-- | @text/javascript@
instance Produces SchemaWebsocketHelp MimeTextjavascript


-- ** Settlement

-- *** settlementGet

-- | @GET \/settlement@
-- 
-- Get settlement history.
-- 
settlementGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest SettlementGet MimeNoContent [Settlement] accept
settlementGet  _ =
  _mkRequest "GET" ["/settlement"]

data SettlementGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam SettlementGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam SettlementGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam SettlementGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam SettlementGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam SettlementGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam SettlementGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam SettlementGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam SettlementGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes SettlementGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes SettlementGet MimeFormUrlEncoded

-- | @application/json@
instance Produces SettlementGet MimeJSON
-- | @application/xml@
instance Produces SettlementGet MimeXML
-- | @text/xml@
instance Produces SettlementGet MimeTextxml
-- | @application/javascript@
instance Produces SettlementGet MimeJavascript
-- | @text/javascript@
instance Produces SettlementGet MimeTextjavascript


-- ** Stats

-- *** statsGet

-- | @GET \/stats@
-- 
-- Get exchange-wide and per-series turnover and volume statistics.
-- 
statsGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest StatsGet MimeNoContent [Stats] accept
statsGet  _ =
  _mkRequest "GET" ["/stats"]

data StatsGet

-- | @application/json@
instance Consumes StatsGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes StatsGet MimeFormUrlEncoded

-- | @application/json@
instance Produces StatsGet MimeJSON
-- | @application/xml@
instance Produces StatsGet MimeXML
-- | @text/xml@
instance Produces StatsGet MimeTextxml
-- | @application/javascript@
instance Produces StatsGet MimeJavascript
-- | @text/javascript@
instance Produces StatsGet MimeTextjavascript


-- *** statsHistory2

-- | @GET \/stats\/history@
-- 
-- Get historical exchange-wide and per-series turnover and volume statistics.
-- 
statsHistory2
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest StatsHistory2 MimeNoContent [StatsHistory] accept
statsHistory2  _ =
  _mkRequest "GET" ["/stats/history"]

data StatsHistory2

-- | @application/json@
instance Consumes StatsHistory2 MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes StatsHistory2 MimeFormUrlEncoded

-- | @application/json@
instance Produces StatsHistory2 MimeJSON
-- | @application/xml@
instance Produces StatsHistory2 MimeXML
-- | @text/xml@
instance Produces StatsHistory2 MimeTextxml
-- | @application/javascript@
instance Produces StatsHistory2 MimeJavascript
-- | @text/javascript@
instance Produces StatsHistory2 MimeTextjavascript


-- *** statsHistoryUSD

-- | @GET \/stats\/historyUSD@
-- 
-- Get a summary of exchange statistics in USD.
-- 
statsHistoryUSD
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest StatsHistoryUSD MimeNoContent [StatsUSD] accept
statsHistoryUSD  _ =
  _mkRequest "GET" ["/stats/historyUSD"]

data StatsHistoryUSD

-- | @application/json@
instance Consumes StatsHistoryUSD MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes StatsHistoryUSD MimeFormUrlEncoded

-- | @application/json@
instance Produces StatsHistoryUSD MimeJSON
-- | @application/xml@
instance Produces StatsHistoryUSD MimeXML
-- | @text/xml@
instance Produces StatsHistoryUSD MimeTextxml
-- | @application/javascript@
instance Produces StatsHistoryUSD MimeJavascript
-- | @text/javascript@
instance Produces StatsHistoryUSD MimeTextjavascript


-- ** Trade

-- *** tradeGet

-- | @GET \/trade@
-- 
-- Get Trades.
-- 
-- Please note that indices (symbols starting with `.`) post trades at intervals to the trade feed. These have a `size` of 0 and are used only to indicate a changing price.  See [the FIX Spec](http://www.onixs.biz/fix-dictionary/5.0.SP2/msgType_AE_6569.html) for explanations of these fields.
-- 
tradeGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest TradeGet MimeNoContent [Trade] accept
tradeGet  _ =
  _mkRequest "GET" ["/trade"]

data TradeGet

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam TradeGet Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam TradeGet Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam TradeGet Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam TradeGet Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam TradeGet Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam TradeGet Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam TradeGet StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam TradeGet EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes TradeGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes TradeGet MimeFormUrlEncoded

-- | @application/json@
instance Produces TradeGet MimeJSON
-- | @application/xml@
instance Produces TradeGet MimeXML
-- | @text/xml@
instance Produces TradeGet MimeTextxml
-- | @application/javascript@
instance Produces TradeGet MimeJavascript
-- | @text/javascript@
instance Produces TradeGet MimeTextjavascript


-- *** tradeGetBucketed

-- | @GET \/trade\/bucketed@
-- 
-- Get previous trades in time buckets.
-- 
tradeGetBucketed
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest TradeGetBucketed MimeNoContent [TradeBin] accept
tradeGetBucketed  _ =
  _mkRequest "GET" ["/trade/bucketed"]

data TradeGetBucketed

-- | /Optional Param/ "binSize" - Time interval to bucket by. Available options: [1m,5m,1h,1d].
instance HasOptionalParam TradeGetBucketed BinSize where
  applyOptionalParam req (BinSize xs) =
    req `setQuery` toQuery ("binSize", Just xs)

-- | /Optional Param/ "partial" - If true, will send in-progress (incomplete) bins for the current time period.
instance HasOptionalParam TradeGetBucketed Partial where
  applyOptionalParam req (Partial xs) =
    req `setQuery` toQuery ("partial", Just xs)

-- | /Optional Param/ "symbol" - Instrument symbol. Send a bare series (e.g. XBU) to get data for the nearest expiring contract in that series.  You can also send a timeframe, e.g. `XBU:monthly`. Timeframes are `daily`, `weekly`, `monthly`, `quarterly`, and `biquarterly`.
instance HasOptionalParam TradeGetBucketed Symbol where
  applyOptionalParam req (Symbol xs) =
    req `setQuery` toQuery ("symbol", Just xs)

-- | /Optional Param/ "filter" - Generic table filter. Send JSON key/value pairs, such as `{\"key\": \"value\"}`. You can key on individual fields, and do more advanced querying on timestamps. See the [Timestamp Docs](https://www.bitmex.com/app/restAPI#timestamp-filters) for more details.
instance HasOptionalParam TradeGetBucketed Filter where
  applyOptionalParam req (Filter xs) =
    req `setQuery` toQuery ("filter", Just xs)

-- | /Optional Param/ "columns" - Array of column names to fetch. If omitted, will return all columns.  Note that this method will always return item keys, even when not specified, so you may receive more columns that you expect.
instance HasOptionalParam TradeGetBucketed Columns where
  applyOptionalParam req (Columns xs) =
    req `setQuery` toQuery ("columns", Just xs)

-- | /Optional Param/ "count" - Number of results to fetch.
instance HasOptionalParam TradeGetBucketed Count where
  applyOptionalParam req (Count xs) =
    req `setQuery` toQuery ("count", Just xs)

-- | /Optional Param/ "start" - Starting point for results.
instance HasOptionalParam TradeGetBucketed Start where
  applyOptionalParam req (Start xs) =
    req `setQuery` toQuery ("start", Just xs)

-- | /Optional Param/ "reverse" - If true, will sort results newest first.
instance HasOptionalParam TradeGetBucketed Reverse where
  applyOptionalParam req (Reverse xs) =
    req `setQuery` toQuery ("reverse", Just xs)

-- | /Optional Param/ "startTime" - Starting date filter for results.
instance HasOptionalParam TradeGetBucketed StartTime where
  applyOptionalParam req (StartTime xs) =
    req `setQuery` toQuery ("startTime", Just xs)

-- | /Optional Param/ "endTime" - Ending date filter for results.
instance HasOptionalParam TradeGetBucketed EndTime where
  applyOptionalParam req (EndTime xs) =
    req `setQuery` toQuery ("endTime", Just xs)

-- | @application/json@
instance Consumes TradeGetBucketed MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes TradeGetBucketed MimeFormUrlEncoded

-- | @application/json@
instance Produces TradeGetBucketed MimeJSON
-- | @application/xml@
instance Produces TradeGetBucketed MimeXML
-- | @text/xml@
instance Produces TradeGetBucketed MimeTextxml
-- | @application/javascript@
instance Produces TradeGetBucketed MimeJavascript
-- | @text/javascript@
instance Produces TradeGetBucketed MimeTextjavascript


-- ** User

-- *** userCancelWithdrawal

-- | @POST \/user\/cancelWithdrawal@
-- 
-- Cancel a withdrawal.
-- 
userCancelWithdrawal
  :: (Consumes UserCancelWithdrawal contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Token -- ^ "token"
  -> BitMEXRequest UserCancelWithdrawal contentType Transaction accept
userCancelWithdrawal _  _ (Token token) =
  _mkRequest "POST" ["/user/cancelWithdrawal"]
    `addForm` toForm ("token", token)

data UserCancelWithdrawal

-- | @application/json@
instance Consumes UserCancelWithdrawal MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserCancelWithdrawal MimeFormUrlEncoded

-- | @application/json@
instance Produces UserCancelWithdrawal MimeJSON
-- | @application/xml@
instance Produces UserCancelWithdrawal MimeXML
-- | @text/xml@
instance Produces UserCancelWithdrawal MimeTextxml
-- | @application/javascript@
instance Produces UserCancelWithdrawal MimeJavascript
-- | @text/javascript@
instance Produces UserCancelWithdrawal MimeTextjavascript


-- *** userCheckReferralCode

-- | @GET \/user\/checkReferralCode@
-- 
-- Check if a referral code is valid.
-- 
-- If the code is valid, responds with the referral code's discount (e.g. `0.1` for 10%). Otherwise, will return a 404.
-- 
userCheckReferralCode
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserCheckReferralCode MimeNoContent Double accept
userCheckReferralCode  _ =
  _mkRequest "GET" ["/user/checkReferralCode"]

data UserCheckReferralCode
instance HasOptionalParam UserCheckReferralCode ReferralCode where
  applyOptionalParam req (ReferralCode xs) =
    req `setQuery` toQuery ("referralCode", Just xs)

-- | @application/json@
instance Consumes UserCheckReferralCode MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserCheckReferralCode MimeFormUrlEncoded

-- | @application/json@
instance Produces UserCheckReferralCode MimeJSON
-- | @application/xml@
instance Produces UserCheckReferralCode MimeXML
-- | @text/xml@
instance Produces UserCheckReferralCode MimeTextxml
-- | @application/javascript@
instance Produces UserCheckReferralCode MimeJavascript
-- | @text/javascript@
instance Produces UserCheckReferralCode MimeTextjavascript


-- *** userConfirm

-- | @POST \/user\/confirmEmail@
-- 
-- Confirm your email address with a token.
-- 
userConfirm
  :: (Consumes UserConfirm contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Token -- ^ "token"
  -> BitMEXRequest UserConfirm contentType AccessToken accept
userConfirm _  _ (Token token) =
  _mkRequest "POST" ["/user/confirmEmail"]
    `addForm` toForm ("token", token)

data UserConfirm

-- | @application/json@
instance Consumes UserConfirm MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserConfirm MimeFormUrlEncoded

-- | @application/json@
instance Produces UserConfirm MimeJSON
-- | @application/xml@
instance Produces UserConfirm MimeXML
-- | @text/xml@
instance Produces UserConfirm MimeTextxml
-- | @application/javascript@
instance Produces UserConfirm MimeJavascript
-- | @text/javascript@
instance Produces UserConfirm MimeTextjavascript


-- *** userConfirmEnableTFA

-- | @POST \/user\/confirmEnableTFA@
-- 
-- Confirm two-factor auth for this account. If using a Yubikey, simply send a token to this endpoint.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userConfirmEnableTFA
  :: (Consumes UserConfirmEnableTFA contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Token -- ^ "token" -  Token from your selected TFA type.
  -> BitMEXRequest UserConfirmEnableTFA contentType Bool accept
userConfirmEnableTFA _  _ (Token token) =
  _mkRequest "POST" ["/user/confirmEnableTFA"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("token", token)

data UserConfirmEnableTFA

-- | /Optional Param/ "type" - Two-factor auth type. Supported types: 'GA' (Google Authenticator), 'Yubikey'
instance HasOptionalParam UserConfirmEnableTFA ParamType where
  applyOptionalParam req (ParamType xs) =
    req `addForm` toForm ("type", xs)

-- | @application/json@
instance Consumes UserConfirmEnableTFA MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserConfirmEnableTFA MimeFormUrlEncoded

-- | @application/json@
instance Produces UserConfirmEnableTFA MimeJSON
-- | @application/xml@
instance Produces UserConfirmEnableTFA MimeXML
-- | @text/xml@
instance Produces UserConfirmEnableTFA MimeTextxml
-- | @application/javascript@
instance Produces UserConfirmEnableTFA MimeJavascript
-- | @text/javascript@
instance Produces UserConfirmEnableTFA MimeTextjavascript


-- *** userConfirmWithdrawal

-- | @POST \/user\/confirmWithdrawal@
-- 
-- Confirm a withdrawal.
-- 
userConfirmWithdrawal
  :: (Consumes UserConfirmWithdrawal contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Token -- ^ "token"
  -> BitMEXRequest UserConfirmWithdrawal contentType Transaction accept
userConfirmWithdrawal _  _ (Token token) =
  _mkRequest "POST" ["/user/confirmWithdrawal"]
    `addForm` toForm ("token", token)

data UserConfirmWithdrawal

-- | @application/json@
instance Consumes UserConfirmWithdrawal MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserConfirmWithdrawal MimeFormUrlEncoded

-- | @application/json@
instance Produces UserConfirmWithdrawal MimeJSON
-- | @application/xml@
instance Produces UserConfirmWithdrawal MimeXML
-- | @text/xml@
instance Produces UserConfirmWithdrawal MimeTextxml
-- | @application/javascript@
instance Produces UserConfirmWithdrawal MimeJavascript
-- | @text/javascript@
instance Produces UserConfirmWithdrawal MimeTextjavascript


-- *** userDisableTFA

-- | @POST \/user\/disableTFA@
-- 
-- Disable two-factor auth for this account.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userDisableTFA
  :: (Consumes UserDisableTFA contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Token -- ^ "token" -  Token from your selected TFA type.
  -> BitMEXRequest UserDisableTFA contentType Bool accept
userDisableTFA _  _ (Token token) =
  _mkRequest "POST" ["/user/disableTFA"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("token", token)

data UserDisableTFA

-- | /Optional Param/ "type" - Two-factor auth type. Supported types: 'GA' (Google Authenticator)
instance HasOptionalParam UserDisableTFA ParamType where
  applyOptionalParam req (ParamType xs) =
    req `addForm` toForm ("type", xs)

-- | @application/json@
instance Consumes UserDisableTFA MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserDisableTFA MimeFormUrlEncoded

-- | @application/json@
instance Produces UserDisableTFA MimeJSON
-- | @application/xml@
instance Produces UserDisableTFA MimeXML
-- | @text/xml@
instance Produces UserDisableTFA MimeTextxml
-- | @application/javascript@
instance Produces UserDisableTFA MimeJavascript
-- | @text/javascript@
instance Produces UserDisableTFA MimeTextjavascript


-- *** userGet

-- | @GET \/user@
-- 
-- Get your user model.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGet MimeNoContent User accept
userGet  _ =
  _mkRequest "GET" ["/user"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGet

-- | @application/json@
instance Consumes UserGet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGet MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGet MimeJSON
-- | @application/xml@
instance Produces UserGet MimeXML
-- | @text/xml@
instance Produces UserGet MimeTextxml
-- | @application/javascript@
instance Produces UserGet MimeJavascript
-- | @text/javascript@
instance Produces UserGet MimeTextjavascript


-- *** userGetAffiliateStatus

-- | @GET \/user\/affiliateStatus@
-- 
-- Get your current affiliate/referral status.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGetAffiliateStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGetAffiliateStatus MimeNoContent Affiliate accept
userGetAffiliateStatus  _ =
  _mkRequest "GET" ["/user/affiliateStatus"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGetAffiliateStatus

-- | @application/json@
instance Consumes UserGetAffiliateStatus MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGetAffiliateStatus MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGetAffiliateStatus MimeJSON
-- | @application/xml@
instance Produces UserGetAffiliateStatus MimeXML
-- | @text/xml@
instance Produces UserGetAffiliateStatus MimeTextxml
-- | @application/javascript@
instance Produces UserGetAffiliateStatus MimeJavascript
-- | @text/javascript@
instance Produces UserGetAffiliateStatus MimeTextjavascript


-- *** userGetCommission

-- | @GET \/user\/commission@
-- 
-- Get your account's commission status.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGetCommission
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGetCommission MimeNoContent [UserCommission] accept
userGetCommission  _ =
  _mkRequest "GET" ["/user/commission"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGetCommission

-- | @application/json@
instance Consumes UserGetCommission MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGetCommission MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGetCommission MimeJSON
-- | @application/xml@
instance Produces UserGetCommission MimeXML
-- | @text/xml@
instance Produces UserGetCommission MimeTextxml
-- | @application/javascript@
instance Produces UserGetCommission MimeJavascript
-- | @text/javascript@
instance Produces UserGetCommission MimeTextjavascript


-- *** userGetDepositAddress

-- | @GET \/user\/depositAddress@
-- 
-- Get a deposit address.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGetDepositAddress
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGetDepositAddress MimeNoContent Text accept
userGetDepositAddress  _ =
  _mkRequest "GET" ["/user/depositAddress"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGetDepositAddress
instance HasOptionalParam UserGetDepositAddress Currency where
  applyOptionalParam req (Currency xs) =
    req `setQuery` toQuery ("currency", Just xs)

-- | @application/json@
instance Consumes UserGetDepositAddress MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGetDepositAddress MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGetDepositAddress MimeJSON
-- | @application/xml@
instance Produces UserGetDepositAddress MimeXML
-- | @text/xml@
instance Produces UserGetDepositAddress MimeTextxml
-- | @application/javascript@
instance Produces UserGetDepositAddress MimeJavascript
-- | @text/javascript@
instance Produces UserGetDepositAddress MimeTextjavascript


-- *** userGetMargin

-- | @GET \/user\/margin@
-- 
-- Get your account's margin status. Send a currency of \"all\" to receive an array of all supported currencies.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGetMargin
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGetMargin MimeNoContent Margin accept
userGetMargin  _ =
  _mkRequest "GET" ["/user/margin"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGetMargin
instance HasOptionalParam UserGetMargin Currency where
  applyOptionalParam req (Currency xs) =
    req `setQuery` toQuery ("currency", Just xs)

-- | @application/json@
instance Consumes UserGetMargin MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGetMargin MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGetMargin MimeJSON
-- | @application/xml@
instance Produces UserGetMargin MimeXML
-- | @text/xml@
instance Produces UserGetMargin MimeTextxml
-- | @application/javascript@
instance Produces UserGetMargin MimeJavascript
-- | @text/javascript@
instance Produces UserGetMargin MimeTextjavascript


-- *** userGetWallet

-- | @GET \/user\/wallet@
-- 
-- Get your current wallet information.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGetWallet
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGetWallet MimeNoContent Wallet accept
userGetWallet  _ =
  _mkRequest "GET" ["/user/wallet"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGetWallet
instance HasOptionalParam UserGetWallet Currency where
  applyOptionalParam req (Currency xs) =
    req `setQuery` toQuery ("currency", Just xs)

-- | @application/json@
instance Consumes UserGetWallet MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGetWallet MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGetWallet MimeJSON
-- | @application/xml@
instance Produces UserGetWallet MimeXML
-- | @text/xml@
instance Produces UserGetWallet MimeTextxml
-- | @application/javascript@
instance Produces UserGetWallet MimeJavascript
-- | @text/javascript@
instance Produces UserGetWallet MimeTextjavascript


-- *** userGetWalletHistory

-- | @GET \/user\/walletHistory@
-- 
-- Get a history of all of your wallet transactions (deposits, withdrawals, PNL).
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGetWalletHistory
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGetWalletHistory MimeNoContent [Transaction] accept
userGetWalletHistory  _ =
  _mkRequest "GET" ["/user/walletHistory"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGetWalletHistory
instance HasOptionalParam UserGetWalletHistory Currency where
  applyOptionalParam req (Currency xs) =
    req `setQuery` toQuery ("currency", Just xs)

-- | @application/json@
instance Consumes UserGetWalletHistory MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGetWalletHistory MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGetWalletHistory MimeJSON
-- | @application/xml@
instance Produces UserGetWalletHistory MimeXML
-- | @text/xml@
instance Produces UserGetWalletHistory MimeTextxml
-- | @application/javascript@
instance Produces UserGetWalletHistory MimeJavascript
-- | @text/javascript@
instance Produces UserGetWalletHistory MimeTextjavascript


-- *** userGetWalletSummary

-- | @GET \/user\/walletSummary@
-- 
-- Get a summary of all of your wallet transactions (deposits, withdrawals, PNL).
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userGetWalletSummary
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserGetWalletSummary MimeNoContent [Transaction] accept
userGetWalletSummary  _ =
  _mkRequest "GET" ["/user/walletSummary"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserGetWalletSummary
instance HasOptionalParam UserGetWalletSummary Currency where
  applyOptionalParam req (Currency xs) =
    req `setQuery` toQuery ("currency", Just xs)

-- | @application/json@
instance Consumes UserGetWalletSummary MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserGetWalletSummary MimeFormUrlEncoded

-- | @application/json@
instance Produces UserGetWalletSummary MimeJSON
-- | @application/xml@
instance Produces UserGetWalletSummary MimeXML
-- | @text/xml@
instance Produces UserGetWalletSummary MimeTextxml
-- | @application/javascript@
instance Produces UserGetWalletSummary MimeJavascript
-- | @text/javascript@
instance Produces UserGetWalletSummary MimeTextjavascript


-- *** userLogout

-- | @POST \/user\/logout@
-- 
-- Log out of BitMEX.
-- 
-- Note: Has 'Produces' instances, but no response schema
-- 
userLogout
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserLogout MimeNoContent res accept
userLogout  _ =
  _mkRequest "POST" ["/user/logout"]

data UserLogout

-- | @application/json@
instance Consumes UserLogout MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserLogout MimeFormUrlEncoded

-- | @application/json@
instance Produces UserLogout MimeJSON
-- | @application/xml@
instance Produces UserLogout MimeXML
-- | @text/xml@
instance Produces UserLogout MimeTextxml
-- | @application/javascript@
instance Produces UserLogout MimeJavascript
-- | @text/javascript@
instance Produces UserLogout MimeTextjavascript


-- *** userLogoutAll

-- | @POST \/user\/logoutAll@
-- 
-- Log all systems out of BitMEX. This will revoke all of your account's access tokens, logging you out on all devices.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userLogoutAll
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserLogoutAll MimeNoContent Double accept
userLogoutAll  _ =
  _mkRequest "POST" ["/user/logoutAll"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserLogoutAll

-- | @application/json@
instance Consumes UserLogoutAll MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserLogoutAll MimeFormUrlEncoded

-- | @application/json@
instance Produces UserLogoutAll MimeJSON
-- | @application/xml@
instance Produces UserLogoutAll MimeXML
-- | @text/xml@
instance Produces UserLogoutAll MimeTextxml
-- | @application/javascript@
instance Produces UserLogoutAll MimeJavascript
-- | @text/javascript@
instance Produces UserLogoutAll MimeTextjavascript


-- *** userMinWithdrawalFee

-- | @GET \/user\/minWithdrawalFee@
-- 
-- Get the minimum withdrawal fee for a currency.
-- 
-- This is changed based on network conditions to ensure timely withdrawals. During network congestion, this may be high. The fee is returned in the same currency.
-- 
userMinWithdrawalFee
  :: Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserMinWithdrawalFee MimeNoContent A.Value accept
userMinWithdrawalFee  _ =
  _mkRequest "GET" ["/user/minWithdrawalFee"]

data UserMinWithdrawalFee
instance HasOptionalParam UserMinWithdrawalFee Currency where
  applyOptionalParam req (Currency xs) =
    req `setQuery` toQuery ("currency", Just xs)

-- | @application/json@
instance Consumes UserMinWithdrawalFee MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserMinWithdrawalFee MimeFormUrlEncoded

-- | @application/json@
instance Produces UserMinWithdrawalFee MimeJSON
-- | @application/xml@
instance Produces UserMinWithdrawalFee MimeXML
-- | @text/xml@
instance Produces UserMinWithdrawalFee MimeTextxml
-- | @application/javascript@
instance Produces UserMinWithdrawalFee MimeJavascript
-- | @text/javascript@
instance Produces UserMinWithdrawalFee MimeTextjavascript


-- *** userRequestEnableTFA

-- | @POST \/user\/requestEnableTFA@
-- 
-- Get secret key for setting up two-factor auth.
-- 
-- Use /confirmEnableTFA directly for Yubikeys. This fails if TFA is already enabled.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userRequestEnableTFA
  :: (Consumes UserRequestEnableTFA contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserRequestEnableTFA contentType Bool accept
userRequestEnableTFA _  _ =
  _mkRequest "POST" ["/user/requestEnableTFA"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserRequestEnableTFA

-- | /Optional Param/ "type" - Two-factor auth type. Supported types: 'GA' (Google Authenticator)
instance HasOptionalParam UserRequestEnableTFA ParamType where
  applyOptionalParam req (ParamType xs) =
    req `addForm` toForm ("type", xs)

-- | @application/json@
instance Consumes UserRequestEnableTFA MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserRequestEnableTFA MimeFormUrlEncoded

-- | @application/json@
instance Produces UserRequestEnableTFA MimeJSON
-- | @application/xml@
instance Produces UserRequestEnableTFA MimeXML
-- | @text/xml@
instance Produces UserRequestEnableTFA MimeTextxml
-- | @application/javascript@
instance Produces UserRequestEnableTFA MimeJavascript
-- | @text/javascript@
instance Produces UserRequestEnableTFA MimeTextjavascript


-- *** userRequestWithdrawal

-- | @POST \/user\/requestWithdrawal@
-- 
-- Request a withdrawal to an external wallet.
-- 
-- This will send a confirmation email to the email address on record, unless requested via an API Key with the `withdraw` permission.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userRequestWithdrawal
  :: (Consumes UserRequestWithdrawal contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Currency -- ^ "currency" -  Currency you're withdrawing. Options: `XBt`
  -> Amount -- ^ "amount" -  Amount of withdrawal currency.
  -> Address -- ^ "address" -  Destination Address.
  -> BitMEXRequest UserRequestWithdrawal contentType Transaction accept
userRequestWithdrawal _  _ (Currency currency) (Amount amount) (Address address) =
  _mkRequest "POST" ["/user/requestWithdrawal"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("currency", currency)
    `addForm` toForm ("amount", amount)
    `addForm` toForm ("address", address)

data UserRequestWithdrawal

-- | /Optional Param/ "otpToken" - 2FA token. Required if 2FA is enabled on your account.
instance HasOptionalParam UserRequestWithdrawal OtpToken where
  applyOptionalParam req (OtpToken xs) =
    req `addForm` toForm ("otpToken", xs)

-- | /Optional Param/ "fee" - Network fee for Bitcoin withdrawals. If not specified, a default value will be calculated based on Bitcoin network conditions. You will have a chance to confirm this via email.
instance HasOptionalParam UserRequestWithdrawal Fee where
  applyOptionalParam req (Fee xs) =
    req `addForm` toForm ("fee", xs)

-- | @application/json@
instance Consumes UserRequestWithdrawal MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserRequestWithdrawal MimeFormUrlEncoded

-- | @application/json@
instance Produces UserRequestWithdrawal MimeJSON
-- | @application/xml@
instance Produces UserRequestWithdrawal MimeXML
-- | @text/xml@
instance Produces UserRequestWithdrawal MimeTextxml
-- | @application/javascript@
instance Produces UserRequestWithdrawal MimeJavascript
-- | @text/javascript@
instance Produces UserRequestWithdrawal MimeTextjavascript


-- *** userSavePreferences

-- | @POST \/user\/preferences@
-- 
-- Save user preferences.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userSavePreferences
  :: (Consumes UserSavePreferences contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Prefs -- ^ "prefs"
  -> BitMEXRequest UserSavePreferences contentType User accept
userSavePreferences _  _ (Prefs prefs) =
  _mkRequest "POST" ["/user/preferences"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)
    `addForm` toForm ("prefs", prefs)

data UserSavePreferences

-- | /Optional Param/ "overwrite" - If true, will overwrite all existing preferences.
instance HasOptionalParam UserSavePreferences Overwrite where
  applyOptionalParam req (Overwrite xs) =
    req `addForm` toForm ("overwrite", xs)

-- | @application/json@
instance Consumes UserSavePreferences MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserSavePreferences MimeFormUrlEncoded

-- | @application/json@
instance Produces UserSavePreferences MimeJSON
-- | @application/xml@
instance Produces UserSavePreferences MimeXML
-- | @text/xml@
instance Produces UserSavePreferences MimeTextxml
-- | @application/javascript@
instance Produces UserSavePreferences MimeJavascript
-- | @text/javascript@
instance Produces UserSavePreferences MimeTextjavascript


-- *** userUpdate

-- | @PUT \/user@
-- 
-- Update your password, name, and other attributes.
-- 
-- AuthMethod: 'AuthApiKeyApiKey', 'AuthApiKeyApiNonce', 'AuthApiKeyApiSignature'
-- 
userUpdate
  :: (Consumes UserUpdate contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> BitMEXRequest UserUpdate contentType User accept
userUpdate _  _ =
  _mkRequest "PUT" ["/user"]
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiKey)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiNonce)
    `_hasAuthType` (P.Proxy :: P.Proxy AuthApiKeyApiSignature)

data UserUpdate
instance HasOptionalParam UserUpdate Firstname where
  applyOptionalParam req (Firstname xs) =
    req `addForm` toForm ("firstname", xs)
instance HasOptionalParam UserUpdate Lastname where
  applyOptionalParam req (Lastname xs) =
    req `addForm` toForm ("lastname", xs)
instance HasOptionalParam UserUpdate OldPassword where
  applyOptionalParam req (OldPassword xs) =
    req `addForm` toForm ("oldPassword", xs)
instance HasOptionalParam UserUpdate NewPassword where
  applyOptionalParam req (NewPassword xs) =
    req `addForm` toForm ("newPassword", xs)
instance HasOptionalParam UserUpdate NewPasswordConfirm where
  applyOptionalParam req (NewPasswordConfirm xs) =
    req `addForm` toForm ("newPasswordConfirm", xs)

-- | /Optional Param/ "username" - Username can only be set once. To reset, email support.
instance HasOptionalParam UserUpdate Username where
  applyOptionalParam req (Username xs) =
    req `addForm` toForm ("username", xs)

-- | /Optional Param/ "country" - Country of residence.
instance HasOptionalParam UserUpdate Country where
  applyOptionalParam req (Country xs) =
    req `addForm` toForm ("country", xs)

-- | /Optional Param/ "pgpPubKey" - PGP Public Key. If specified, automated emails will be sentwith this key.
instance HasOptionalParam UserUpdate PgpPubKey where
  applyOptionalParam req (PgpPubKey xs) =
    req `addForm` toForm ("pgpPubKey", xs)

-- | @application/json@
instance Consumes UserUpdate MimeJSON
-- | @application/x-www-form-urlencoded@
instance Consumes UserUpdate MimeFormUrlEncoded

-- | @application/json@
instance Produces UserUpdate MimeJSON
-- | @application/xml@
instance Produces UserUpdate MimeXML
-- | @text/xml@
instance Produces UserUpdate MimeTextxml
-- | @application/javascript@
instance Produces UserUpdate MimeJavascript
-- | @text/javascript@
instance Produces UserUpdate MimeTextjavascript



-- * Parameter newtypes

newtype Account = Account { unAccount :: Double } deriving (P.Eq, P.Show)
newtype Address = Address { unAddress :: Text } deriving (P.Eq, P.Show)
newtype Amount = Amount { unAmount :: Double } deriving (P.Eq, P.Show)
newtype ApiKeyId = ApiKeyId { unApiKeyId :: Text } deriving (P.Eq, P.Show)
newtype BinSize = BinSize { unBinSize :: Text } deriving (P.Eq, P.Show)
newtype ChannelId = ChannelId { unChannelId :: Double } deriving (P.Eq, P.Show)
newtype Cidr = Cidr { unCidr :: Text } deriving (P.Eq, P.Show)
newtype ClOrdId = ClOrdId { unClOrdId :: Text } deriving (P.Eq, P.Show)
newtype ClOrdLinkId = ClOrdLinkId { unClOrdLinkId :: Text } deriving (P.Eq, P.Show)
newtype Columns = Columns { unColumns :: Text } deriving (P.Eq, P.Show)
newtype ContingencyType = ContingencyType { unContingencyType :: Text } deriving (P.Eq, P.Show)
newtype Count = Count { unCount :: Double } deriving (P.Eq, P.Show)
newtype Country = Country { unCountry :: Text } deriving (P.Eq, P.Show)
newtype Currency = Currency { unCurrency :: Text } deriving (P.Eq, P.Show)
newtype Depth = Depth { unDepth :: Double } deriving (P.Eq, P.Show)
newtype DisplayQty = DisplayQty { unDisplayQty :: Double } deriving (P.Eq, P.Show)
newtype Enabled = Enabled { unEnabled :: Bool } deriving (P.Eq, P.Show)
newtype EndTime = EndTime { unEndTime :: DateTime } deriving (P.Eq, P.Show)
newtype ExecInst = ExecInst { unExecInst :: Text } deriving (P.Eq, P.Show)
newtype Fee = Fee { unFee :: Double } deriving (P.Eq, P.Show)
newtype Filter = Filter { unFilter :: Text } deriving (P.Eq, P.Show)
newtype Firstname = Firstname { unFirstname :: Text } deriving (P.Eq, P.Show)
newtype Lastname = Lastname { unLastname :: Text } deriving (P.Eq, P.Show)
newtype LeavesQty = LeavesQty { unLeavesQty :: Double } deriving (P.Eq, P.Show)
newtype Leverage = Leverage { unLeverage :: Double } deriving (P.Eq, P.Show)
newtype Message = Message { unMessage :: Text } deriving (P.Eq, P.Show)
newtype Method = Method { unMethod :: Text } deriving (P.Eq, P.Show)
newtype Model = Model { unModel :: Text } deriving (P.Eq, P.Show)
newtype Name = Name { unName :: Text } deriving (P.Eq, P.Show)
newtype NewPassword = NewPassword { unNewPassword :: Text } deriving (P.Eq, P.Show)
newtype NewPasswordConfirm = NewPasswordConfirm { unNewPasswordConfirm :: Text } deriving (P.Eq, P.Show)
newtype OldPassword = OldPassword { unOldPassword :: Text } deriving (P.Eq, P.Show)
newtype OrdType = OrdType { unOrdType :: Text } deriving (P.Eq, P.Show)
newtype OrderId = OrderId { unOrderId :: Text } deriving (P.Eq, P.Show)
newtype OrderQty = OrderQty { unOrderQty :: Double } deriving (P.Eq, P.Show)
newtype Orders = Orders { unOrders :: Text } deriving (P.Eq, P.Show)
newtype OrigClOrdId = OrigClOrdId { unOrigClOrdId :: Text } deriving (P.Eq, P.Show)
newtype OtpToken = OtpToken { unOtpToken :: Text } deriving (P.Eq, P.Show)
newtype Overwrite = Overwrite { unOverwrite :: Bool } deriving (P.Eq, P.Show)
newtype ParamText = ParamText { unParamText :: Text } deriving (P.Eq, P.Show)
newtype ParamType = ParamType { unParamType :: Text } deriving (P.Eq, P.Show)
newtype Partial = Partial { unPartial :: Bool } deriving (P.Eq, P.Show)
newtype PegOffsetValue = PegOffsetValue { unPegOffsetValue :: Double } deriving (P.Eq, P.Show)
newtype PegPriceType = PegPriceType { unPegPriceType :: Text } deriving (P.Eq, P.Show)
newtype Permissions = Permissions { unPermissions :: Text } deriving (P.Eq, P.Show)
newtype PgpPubKey = PgpPubKey { unPgpPubKey :: Text } deriving (P.Eq, P.Show)
newtype Prefs = Prefs { unPrefs :: Text } deriving (P.Eq, P.Show)
newtype Price = Price { unPrice :: Double } deriving (P.Eq, P.Show)
newtype Quantity = Quantity { unQuantity :: Double } deriving (P.Eq, P.Show)
newtype ReferralCode = ReferralCode { unReferralCode :: Text } deriving (P.Eq, P.Show)
newtype Reverse = Reverse { unReverse :: Bool } deriving (P.Eq, P.Show)
newtype RiskLimit = RiskLimit { unRiskLimit :: Double } deriving (P.Eq, P.Show)
newtype Side = Side { unSide :: Text } deriving (P.Eq, P.Show)
newtype SimpleLeavesQty = SimpleLeavesQty { unSimpleLeavesQty :: Double } deriving (P.Eq, P.Show)
newtype SimpleOrderQty = SimpleOrderQty { unSimpleOrderQty :: Double } deriving (P.Eq, P.Show)
newtype Start = Start { unStart :: Double } deriving (P.Eq, P.Show)
newtype StartTime = StartTime { unStartTime :: DateTime } deriving (P.Eq, P.Show)
newtype StopPrice = StopPrice { unStopPrice :: Double } deriving (P.Eq, P.Show)
newtype StopPx = StopPx { unStopPx :: Double } deriving (P.Eq, P.Show)
newtype Symbol = Symbol { unSymbol :: Text } deriving (P.Eq, P.Show)
newtype TimeInForce = TimeInForce { unTimeInForce :: Text } deriving (P.Eq, P.Show)
newtype Timeout = Timeout { unTimeout :: Double } deriving (P.Eq, P.Show)
newtype Token = Token { unToken :: Text } deriving (P.Eq, P.Show)
newtype Username = Username { unUsername :: Text } deriving (P.Eq, P.Show)

-- * Auth Methods

-- ** AuthApiKeyApiKey
data AuthApiKeyApiKey =
  AuthApiKeyApiKey Text -- ^ secret
  deriving (P.Eq, P.Show, P.Typeable)

instance AuthMethod AuthApiKeyApiKey where
  applyAuthMethod _ a@(AuthApiKeyApiKey secret) req =
    P.pure $
    if (P.typeOf a `P.elem` rAuthTypes req)
      then req `setHeader` toHeader ("api-key", secret)
           & L.over rAuthTypesL (P.filter (/= P.typeOf a))
      else req

-- ** AuthApiKeyApiNonce
data AuthApiKeyApiNonce =
  AuthApiKeyApiNonce Text -- ^ secret
  deriving (P.Eq, P.Show, P.Typeable)

instance AuthMethod AuthApiKeyApiNonce where
  applyAuthMethod _ a@(AuthApiKeyApiNonce secret) req =
    P.pure $
    if (P.typeOf a `P.elem` rAuthTypes req)
      then req `setHeader` toHeader ("api-nonce", secret)
           & L.over rAuthTypesL (P.filter (/= P.typeOf a))
      else req

-- ** AuthApiKeyApiSignature
data AuthApiKeyApiSignature =
  AuthApiKeyApiSignature Text -- ^ secret
  deriving (P.Eq, P.Show, P.Typeable)

instance AuthMethod AuthApiKeyApiSignature where
  applyAuthMethod _ a@(AuthApiKeyApiSignature secret) req =
    P.pure $
    if (P.typeOf a `P.elem` rAuthTypes req)
      then req `setHeader` toHeader ("api-signature", secret)
           & L.over rAuthTypesL (P.filter (/= P.typeOf a))
      else req



-- * Custom Mime Types

-- ** MimeJavascript

data MimeJavascript = MimeJavascript deriving (P.Typeable)

-- | @application/javascript@
instance MimeType MimeJavascript where
  mimeType _ = Just $ P.fromString "application/javascript"
-- instance MimeRender MimeJavascript T.Text where mimeRender _ = undefined
-- instance MimeUnrender MimeJavascript T.Text where mimeUnrender _ = undefined

-- ** MimeTextjavascript

data MimeTextjavascript = MimeTextjavascript deriving (P.Typeable)

-- | @text/javascript@
instance MimeType MimeTextjavascript where
  mimeType _ = Just $ P.fromString "text/javascript"
-- instance MimeRender MimeTextjavascript T.Text where mimeRender _ = undefined
-- instance MimeUnrender MimeTextjavascript T.Text where mimeUnrender _ = undefined

-- ** MimeTextxml

data MimeTextxml = MimeTextxml deriving (P.Typeable)

-- | @text/xml@
instance MimeType MimeTextxml where
  mimeType _ = Just $ P.fromString "text/xml"
-- instance MimeRender MimeTextxml T.Text where mimeRender _ = undefined
-- instance MimeUnrender MimeTextxml T.Text where mimeUnrender _ = undefined