gdax-0.6.0.0: API Wrapping for Coinbase's GDAX exchange.

Safe HaskellNone
LanguageHaskell2010

Network.GDAX.Types.Shared

Documentation

newtype AccountId Source #

Constructors

AccountId 

Fields

newtype UserId Source #

Constructors

UserId 

Fields

Instances

Eq UserId Source # 

Methods

(==) :: UserId -> UserId -> Bool #

(/=) :: UserId -> UserId -> Bool #

Ord UserId Source # 
Show UserId Source # 
IsString UserId Source # 

Methods

fromString :: String -> UserId #

Generic UserId Source # 

Associated Types

type Rep UserId :: * -> * #

Methods

from :: UserId -> Rep UserId x #

to :: Rep UserId x -> UserId #

Hashable UserId Source # 

Methods

hashWithSalt :: Int -> UserId -> Int #

hash :: UserId -> Int #

ToJSON UserId Source # 
FromJSON UserId Source # 
type Rep UserId Source # 
type Rep UserId = D1 (MetaData "UserId" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "UserId" PrefixI True) (S1 (MetaSel (Just Symbol "unUserId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ProfileId Source #

Constructors

ProfileId 

Fields

newtype OrderId Source #

Constructors

OrderId 

Fields

data OrderType Source #

Constructors

OrderLimit 
OrderMarket 

Instances

Show OrderType Source # 
Generic OrderType Source # 

Associated Types

type Rep OrderType :: * -> * #

Hashable OrderType Source # 
FromJSON OrderType Source # 
type Rep OrderType Source # 
type Rep OrderType = D1 (MetaData "OrderType" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" False) ((:+:) (C1 (MetaCons "OrderLimit" PrefixI False) U1) (C1 (MetaCons "OrderMarket" PrefixI False) U1))

newtype StopType Source #

Constructors

StopType 

Fields

newtype ProductId Source #

Constructors

ProductId 

Fields

Instances

Eq ProductId Source # 
Ord ProductId Source # 
Show ProductId Source # 
IsString ProductId Source # 
Generic ProductId Source # 

Associated Types

type Rep ProductId :: * -> * #

Hashable ProductId Source # 
ToJSON ProductId Source # 
FromJSON ProductId Source # 
type Rep ProductId Source # 
type Rep ProductId = D1 (MetaData "ProductId" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "ProductId" PrefixI True) (S1 (MetaSel (Just Symbol "unProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Sequence Source #

Constructors

Sequence 

Fields

Instances

Enum Sequence Source # 
Eq Sequence Source # 
Ord Sequence Source # 
Show Sequence Source # 
Generic Sequence Source # 

Associated Types

type Rep Sequence :: * -> * #

Methods

from :: Sequence -> Rep Sequence x #

to :: Rep Sequence x -> Sequence #

Hashable Sequence Source # 

Methods

hashWithSalt :: Int -> Sequence -> Int #

hash :: Sequence -> Int #

ToJSON Sequence Source # 
FromJSON Sequence Source # 
type Rep Sequence Source # 
type Rep Sequence = D1 (MetaData "Sequence" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "Sequence" PrefixI True) (S1 (MetaSel (Just Symbol "unSequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

newtype TradeId Source #

Constructors

TradeId 

Fields

Instances

data Side Source #

Constructors

Buy 
Sell 

Instances

Show Side Source # 

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Generic Side Source # 

Associated Types

type Rep Side :: * -> * #

Methods

from :: Side -> Rep Side x #

to :: Rep Side x -> Side #

Hashable Side Source # 

Methods

hashWithSalt :: Int -> Side -> Int #

hash :: Side -> Int #

ToJSON Side Source # 
FromJSON Side Source # 
type Rep Side Source # 
type Rep Side = D1 (MetaData "Side" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" False) ((:+:) (C1 (MetaCons "Buy" PrefixI False) U1) (C1 (MetaCons "Sell" PrefixI False) U1))

newtype CurrencyId Source #

Constructors

CurrencyId 

Fields

Instances

Eq CurrencyId Source # 
Ord CurrencyId Source # 
Show CurrencyId Source # 
IsString CurrencyId Source # 
Generic CurrencyId Source # 

Associated Types

type Rep CurrencyId :: * -> * #

Hashable CurrencyId Source # 
ToJSON CurrencyId Source # 
FromJSON CurrencyId Source # 
type Rep CurrencyId Source # 
type Rep CurrencyId = D1 (MetaData "CurrencyId" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "CurrencyId" PrefixI True) (S1 (MetaSel (Just Symbol "unCurrencyId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype EntryId Source #

Constructors

EntryId 

Fields

data EntryType Source #

Instances

Eq EntryType Source # 
Show EntryType Source # 
Generic EntryType Source # 

Associated Types

type Rep EntryType :: * -> * #

Hashable EntryType Source # 
FromJSON EntryType Source # 
type Rep EntryType Source # 
type Rep EntryType = D1 (MetaData "EntryType" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" False) ((:+:) (C1 (MetaCons "EntryMatch" PrefixI False) U1) ((:+:) (C1 (MetaCons "EntryFee" PrefixI False) U1) (C1 (MetaCons "EntryTransfer" PrefixI False) U1)))

newtype TransferId Source #

Constructors

TransferId 

Fields

newtype HoldId Source #

Constructors

HoldId 

Fields

Instances

Eq HoldId Source # 

Methods

(==) :: HoldId -> HoldId -> Bool #

(/=) :: HoldId -> HoldId -> Bool #

Ord HoldId Source # 
Show HoldId Source # 
Generic HoldId Source # 

Associated Types

type Rep HoldId :: * -> * #

Methods

from :: HoldId -> Rep HoldId x #

to :: Rep HoldId x -> HoldId #

Hashable HoldId Source # 

Methods

hashWithSalt :: Int -> HoldId -> Int #

hash :: HoldId -> Int #

ToJSON HoldId Source # 
FromJSON HoldId Source # 
type Rep HoldId Source # 
type Rep HoldId = D1 (MetaData "HoldId" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "HoldId" PrefixI True) (S1 (MetaSel (Just Symbol "unHoldId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

newtype ClientOrderId Source #

Constructors

ClientOrderId 

Instances

Eq ClientOrderId Source # 
Ord ClientOrderId Source # 
Show ClientOrderId Source # 
Generic ClientOrderId Source # 

Associated Types

type Rep ClientOrderId :: * -> * #

Hashable ClientOrderId Source # 
ToJSON ClientOrderId Source # 
FromJSON ClientOrderId Source # 
type Rep ClientOrderId Source # 
type Rep ClientOrderId = D1 (MetaData "ClientOrderId" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "ClientOrderId" PrefixI True) (S1 (MetaSel (Just Symbol "unClientOrderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data Liquidity Source #

Instances

Show Liquidity Source # 
Generic Liquidity Source # 

Associated Types

type Rep Liquidity :: * -> * #

Hashable Liquidity Source # 
ToJSON Liquidity Source # 
FromJSON Liquidity Source # 
type Rep Liquidity Source # 
type Rep Liquidity = D1 (MetaData "Liquidity" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" False) ((:+:) (C1 (MetaCons "LiquidityMaker" PrefixI False) U1) (C1 (MetaCons "LiquidityTaker" PrefixI False) U1))

newtype FundingId Source #

Constructors

FundingId 

Fields

data MarginType Source #

Instances

Show MarginType Source # 
Generic MarginType Source # 

Associated Types

type Rep MarginType :: * -> * #

Hashable MarginType Source # 
ToJSON MarginType Source # 
FromJSON MarginType Source # 
type Rep MarginType Source # 
type Rep MarginType = D1 (MetaData "MarginType" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" False) ((:+:) (C1 (MetaCons "MarginDeposit" PrefixI False) U1) (C1 (MetaCons "MarginWithdraw" PrefixI False) U1))

newtype MarginTransferId Source #

Constructors

MarginTransferId 

Instances

Eq MarginTransferId Source # 
Ord MarginTransferId Source # 
Show MarginTransferId Source # 
Generic MarginTransferId Source # 
Hashable MarginTransferId Source # 
ToJSON MarginTransferId Source # 
FromJSON MarginTransferId Source # 
type Rep MarginTransferId Source # 
type Rep MarginTransferId = D1 (MetaData "MarginTransferId" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "MarginTransferId" PrefixI True) (S1 (MetaSel (Just Symbol "unMarginTransferId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

newtype PaymentMethodId Source #

Constructors

PaymentMethodId 

Instances

Eq PaymentMethodId Source # 
Ord PaymentMethodId Source # 
Show PaymentMethodId Source # 
Generic PaymentMethodId Source # 
Hashable PaymentMethodId Source # 
ToJSON PaymentMethodId Source # 
FromJSON PaymentMethodId Source # 
type Rep PaymentMethodId Source # 
type Rep PaymentMethodId = D1 (MetaData "PaymentMethodId" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" True) (C1 (MetaCons "PaymentMethodId" PrefixI True) (S1 (MetaSel (Just Symbol "unPaymentMethodId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

newtype DepositId Source #

Constructors

DepositId 

Fields

newtype WithdrawId Source #

Constructors

WithdrawId 

Fields

data PaymentMethodType Source #

Instances

Eq PaymentMethodType Source # 
Ord PaymentMethodType Source # 
Show PaymentMethodType Source # 
Generic PaymentMethodType Source # 
Hashable PaymentMethodType Source # 
ToJSON PaymentMethodType Source # 
FromJSON PaymentMethodType Source # 
type Rep PaymentMethodType Source # 
type Rep PaymentMethodType = D1 (MetaData "PaymentMethodType" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" False) ((:+:) (C1 (MetaCons "MethodFiatAccount" PrefixI False) U1) ((:+:) (C1 (MetaCons "MethodBankWire" PrefixI False) U1) (C1 (MetaCons "MethodACHBankAccount" PrefixI False) U1)))

data ReportType Source #

Constructors

ReportFills 
ReportAccount 

Instances

Show ReportType Source # 
Generic ReportType Source # 

Associated Types

type Rep ReportType :: * -> * #

Hashable ReportType Source # 
ToJSON ReportType Source # 
FromJSON ReportType Source # 
type Rep ReportType Source # 
type Rep ReportType = D1 (MetaData "ReportType" "Network.GDAX.Types.Shared" "gdax-0.6.0.0-F40861Q8gvHAPG8RopSKgw" False) ((:+:) (C1 (MetaCons "ReportFills" PrefixI False) U1) (C1 (MetaCons "ReportAccount" PrefixI False) U1))