coinbase-exchange-0.4.0.0: Connector library for the coinbase exchange.

Safe HaskellNone
LanguageHaskell2010

Coinbase.Exchange.Types.Private

Documentation

newtype AccountId Source #

Constructors

AccountId 

Fields

Instances

Eq AccountId Source # 
Data AccountId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountId -> c AccountId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountId #

toConstr :: AccountId -> Constr #

dataTypeOf :: AccountId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountId) #

gmapT :: (forall b. Data b => b -> b) -> AccountId -> AccountId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId #

Ord AccountId Source # 
Read AccountId Source # 
Show AccountId Source # 
Generic AccountId Source # 

Associated Types

type Rep AccountId :: * -> * #

Hashable AccountId Source # 
ToJSON AccountId Source # 
FromJSON AccountId Source # 
NFData AccountId Source # 

Methods

rnf :: AccountId -> () #

type Rep AccountId Source # 
type Rep AccountId = D1 (MetaData "AccountId" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "AccountId" PrefixI True) (S1 (MetaSel (Just Symbol "unAccountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data Account Source #

Instances

Eq Account Source # 

Methods

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

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

Data Account Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account #

toConstr :: Account -> Constr #

dataTypeOf :: Account -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Account) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) #

gmapT :: (forall b. Data b => b -> b) -> Account -> Account #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

Show Account Source # 
Generic Account Source # 

Associated Types

type Rep Account :: * -> * #

Methods

from :: Account -> Rep Account x #

to :: Rep Account x -> Account #

ToJSON Account Source # 
FromJSON Account Source # 
NFData Account Source # 

Methods

rnf :: Account -> () #

type Rep Account Source # 

newtype EntryId Source #

Constructors

EntryId 

Fields

Instances

Eq EntryId Source # 

Methods

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

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

Data EntryId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EntryId -> c EntryId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EntryId #

toConstr :: EntryId -> Constr #

dataTypeOf :: EntryId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EntryId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EntryId) #

gmapT :: (forall b. Data b => b -> b) -> EntryId -> EntryId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EntryId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EntryId -> r #

gmapQ :: (forall d. Data d => d -> u) -> EntryId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EntryId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EntryId -> m EntryId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EntryId -> m EntryId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EntryId -> m EntryId #

Num EntryId Source # 
Ord EntryId Source # 
Read EntryId Source # 
Show EntryId Source # 
Generic EntryId Source # 

Associated Types

type Rep EntryId :: * -> * #

Methods

from :: EntryId -> Rep EntryId x #

to :: Rep EntryId x -> EntryId #

Hashable EntryId Source # 

Methods

hashWithSalt :: Int -> EntryId -> Int #

hash :: EntryId -> Int #

ToJSON EntryId Source # 
FromJSON EntryId Source # 
NFData EntryId Source # 

Methods

rnf :: EntryId -> () #

type Rep EntryId Source # 
type Rep EntryId = D1 (MetaData "EntryId" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "EntryId" PrefixI True) (S1 (MetaSel (Just Symbol "unEntryId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

data Entry Source #

Instances

Data Entry Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Entry -> c Entry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Entry #

toConstr :: Entry -> Constr #

dataTypeOf :: Entry -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Entry) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Entry) #

gmapT :: (forall b. Data b => b -> b) -> Entry -> Entry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Entry -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Entry -> r #

gmapQ :: (forall d. Data d => d -> u) -> Entry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Entry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Entry -> m Entry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Entry -> m Entry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Entry -> m Entry #

Show Entry Source # 

Methods

showsPrec :: Int -> Entry -> ShowS #

show :: Entry -> String #

showList :: [Entry] -> ShowS #

Generic Entry Source # 

Associated Types

type Rep Entry :: * -> * #

Methods

from :: Entry -> Rep Entry x #

to :: Rep Entry x -> Entry #

ToJSON Entry Source # 
FromJSON Entry Source # 
NFData Entry Source # 

Methods

rnf :: Entry -> () #

type Rep Entry Source # 

data EntryType Source #

Constructors

Match 
Fee 
Transfer 

Instances

Eq EntryType Source # 
Data EntryType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EntryType -> c EntryType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EntryType #

toConstr :: EntryType -> Constr #

dataTypeOf :: EntryType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EntryType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EntryType) #

gmapT :: (forall b. Data b => b -> b) -> EntryType -> EntryType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EntryType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EntryType -> r #

gmapQ :: (forall d. Data d => d -> u) -> EntryType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EntryType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EntryType -> m EntryType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EntryType -> m EntryType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EntryType -> m EntryType #

Ord EntryType Source # 
Read EntryType Source # 
Show EntryType Source # 
Generic EntryType Source # 

Associated Types

type Rep EntryType :: * -> * #

Hashable EntryType Source # 
ToJSON EntryType Source # 
FromJSON EntryType Source # 
NFData EntryType Source # 

Methods

rnf :: EntryType -> () #

type Rep EntryType Source # 
type Rep EntryType = D1 (MetaData "EntryType" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "Match" PrefixI False) U1) ((:+:) (C1 (MetaCons "Fee" PrefixI False) U1) (C1 (MetaCons "Transfer" PrefixI False) U1)))

data EntryDetails Source #

Instances

Data EntryDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EntryDetails -> c EntryDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EntryDetails #

toConstr :: EntryDetails -> Constr #

dataTypeOf :: EntryDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EntryDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EntryDetails) #

gmapT :: (forall b. Data b => b -> b) -> EntryDetails -> EntryDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EntryDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EntryDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> EntryDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EntryDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EntryDetails -> m EntryDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EntryDetails -> m EntryDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EntryDetails -> m EntryDetails #

Show EntryDetails Source # 
Generic EntryDetails Source # 

Associated Types

type Rep EntryDetails :: * -> * #

ToJSON EntryDetails Source # 
FromJSON EntryDetails Source # 
NFData EntryDetails Source # 

Methods

rnf :: EntryDetails -> () #

type Rep EntryDetails Source # 
type Rep EntryDetails = D1 (MetaData "EntryDetails" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "EntryDetails" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "detailOrderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OrderId))) ((:*:) (S1 (MetaSel (Just Symbol "detailTradeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe TradeId))) (S1 (MetaSel (Just Symbol "detailProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ProductId))))))

newtype HoldId Source #

Constructors

HoldId 

Fields

Instances

Eq HoldId Source # 

Methods

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

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

Data HoldId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HoldId -> c HoldId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HoldId #

toConstr :: HoldId -> Constr #

dataTypeOf :: HoldId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c HoldId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HoldId) #

gmapT :: (forall b. Data b => b -> b) -> HoldId -> HoldId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HoldId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HoldId -> r #

gmapQ :: (forall d. Data d => d -> u) -> HoldId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HoldId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HoldId -> m HoldId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HoldId -> m HoldId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HoldId -> m HoldId #

Ord HoldId Source # 
Read 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 # 
NFData HoldId Source # 

Methods

rnf :: HoldId -> () #

type Rep HoldId Source # 
type Rep HoldId = D1 (MetaData "HoldId" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "HoldId" PrefixI True) (S1 (MetaSel (Just Symbol "unHoldId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data Hold Source #

Instances

Data Hold Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Hold -> c Hold #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Hold #

toConstr :: Hold -> Constr #

dataTypeOf :: Hold -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Hold) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Hold) #

gmapT :: (forall b. Data b => b -> b) -> Hold -> Hold #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hold -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hold -> r #

gmapQ :: (forall d. Data d => d -> u) -> Hold -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Hold -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Hold -> m Hold #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Hold -> m Hold #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Hold -> m Hold #

Show Hold Source # 

Methods

showsPrec :: Int -> Hold -> ShowS #

show :: Hold -> String #

showList :: [Hold] -> ShowS #

Generic Hold Source # 

Associated Types

type Rep Hold :: * -> * #

Methods

from :: Hold -> Rep Hold x #

to :: Rep Hold x -> Hold #

ToJSON Hold Source # 
FromJSON Hold Source # 
NFData Hold Source # 

Methods

rnf :: Hold -> () #

type Rep Hold Source # 
type Rep Hold = D1 (MetaData "Hold" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "OrderHold" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "holdId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HoldId)) ((:*:) (S1 (MetaSel (Just Symbol "holdAccountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccountId)) (S1 (MetaSel (Just Symbol "holdCreatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))) ((:*:) (S1 (MetaSel (Just Symbol "holdUpdatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) ((:*:) (S1 (MetaSel (Just Symbol "holdAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinScientific)) (S1 (MetaSel (Just Symbol "holdOrderRef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderId)))))) (C1 (MetaCons "TransferHold" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "holdId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HoldId)) ((:*:) (S1 (MetaSel (Just Symbol "holdAccountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AccountId)) (S1 (MetaSel (Just Symbol "holdCreatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))) ((:*:) (S1 (MetaSel (Just Symbol "holdUpdatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) ((:*:) (S1 (MetaSel (Just Symbol "holdAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinScientific)) (S1 (MetaSel (Just Symbol "holdTransferRef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransferId)))))))

data OrderContigency Source #

Instances

Eq OrderContigency Source # 
Data OrderContigency Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderContigency -> c OrderContigency #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderContigency #

toConstr :: OrderContigency -> Constr #

dataTypeOf :: OrderContigency -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderContigency) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderContigency) #

gmapT :: (forall b. Data b => b -> b) -> OrderContigency -> OrderContigency #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderContigency -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderContigency -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderContigency -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderContigency -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderContigency -> m OrderContigency #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderContigency -> m OrderContigency #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderContigency -> m OrderContigency #

Ord OrderContigency Source # 
Read OrderContigency Source # 
Show OrderContigency Source # 
Generic OrderContigency Source # 
Hashable OrderContigency Source # 
ToJSON OrderContigency Source # 
FromJSON OrderContigency Source # 
NFData OrderContigency Source # 

Methods

rnf :: OrderContigency -> () #

type Rep OrderContigency Source # 
type Rep OrderContigency = D1 (MetaData "OrderContigency" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) ((:+:) (C1 (MetaCons "GoodTillCanceled" PrefixI False) U1) (C1 (MetaCons "GoodTillTime" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ImmediateOrCancel" PrefixI False) U1) (C1 (MetaCons "FillOrKill" PrefixI False) U1)))

data OrderCancelAfter Source #

Constructors

Min 
Hour 
Day 

Instances

Eq OrderCancelAfter Source # 
Data OrderCancelAfter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderCancelAfter -> c OrderCancelAfter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderCancelAfter #

toConstr :: OrderCancelAfter -> Constr #

dataTypeOf :: OrderCancelAfter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderCancelAfter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderCancelAfter) #

gmapT :: (forall b. Data b => b -> b) -> OrderCancelAfter -> OrderCancelAfter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderCancelAfter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderCancelAfter -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderCancelAfter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderCancelAfter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderCancelAfter -> m OrderCancelAfter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderCancelAfter -> m OrderCancelAfter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderCancelAfter -> m OrderCancelAfter #

Ord OrderCancelAfter Source # 
Read OrderCancelAfter Source # 
Show OrderCancelAfter Source # 
Generic OrderCancelAfter Source # 
Hashable OrderCancelAfter Source # 
ToJSON OrderCancelAfter Source # 
FromJSON OrderCancelAfter Source # 
NFData OrderCancelAfter Source # 

Methods

rnf :: OrderCancelAfter -> () #

type Rep OrderCancelAfter Source # 
type Rep OrderCancelAfter = D1 (MetaData "OrderCancelAfter" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "Min" PrefixI False) U1) ((:+:) (C1 (MetaCons "Hour" PrefixI False) U1) (C1 (MetaCons "Day" PrefixI False) U1)))

data SelfTrade Source #

Instances

Eq SelfTrade Source # 
Data SelfTrade Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelfTrade -> c SelfTrade #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelfTrade #

toConstr :: SelfTrade -> Constr #

dataTypeOf :: SelfTrade -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SelfTrade) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelfTrade) #

gmapT :: (forall b. Data b => b -> b) -> SelfTrade -> SelfTrade #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelfTrade -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelfTrade -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelfTrade -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelfTrade -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelfTrade -> m SelfTrade #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelfTrade -> m SelfTrade #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelfTrade -> m SelfTrade #

Ord SelfTrade Source # 
Read SelfTrade Source # 
Show SelfTrade Source # 
Generic SelfTrade Source # 

Associated Types

type Rep SelfTrade :: * -> * #

Hashable SelfTrade Source # 
ToJSON SelfTrade Source # 
FromJSON SelfTrade Source # 
NFData SelfTrade Source # 

Methods

rnf :: SelfTrade -> () #

type Rep SelfTrade Source # 
type Rep SelfTrade = D1 (MetaData "SelfTrade" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) ((:+:) (C1 (MetaCons "DecrementAndCancel" PrefixI False) U1) (C1 (MetaCons "CancelOldest" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CancelNewest" PrefixI False) U1) (C1 (MetaCons "CancelBoth" PrefixI False) U1)))

data NewOrder Source #

Instances

Data NewOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewOrder -> c NewOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewOrder #

toConstr :: NewOrder -> Constr #

dataTypeOf :: NewOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewOrder) #

gmapT :: (forall b. Data b => b -> b) -> NewOrder -> NewOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewOrder -> m NewOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewOrder -> m NewOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewOrder -> m NewOrder #

Show NewOrder Source # 
Generic NewOrder Source # 

Associated Types

type Rep NewOrder :: * -> * #

Methods

from :: NewOrder -> Rep NewOrder x #

to :: Rep NewOrder x -> NewOrder #

ToJSON NewOrder Source # 
NFData NewOrder Source # 

Methods

rnf :: NewOrder -> () #

type Rep NewOrder Source # 
type Rep NewOrder = D1 (MetaData "NewOrder" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "NewLimitOrder" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "noProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProductId)) (S1 (MetaSel (Just Symbol "noSide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Side))) ((:*:) (S1 (MetaSel (Just Symbol "noSelfTrade") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SelfTrade)) (S1 (MetaSel (Just Symbol "noClientOid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ClientOrderId))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "noPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Price)) (S1 (MetaSel (Just Symbol "noSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size))) ((:*:) (S1 (MetaSel (Just Symbol "noTimeInForce") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderContigency)) ((:*:) (S1 (MetaSel (Just Symbol "noCancelAfter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OrderCancelAfter))) (S1 (MetaSel (Just Symbol "noPostOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))))) ((:+:) (C1 (MetaCons "NewMarketOrder" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "noProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProductId)) (S1 (MetaSel (Just Symbol "noSide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Side))) ((:*:) (S1 (MetaSel (Just Symbol "noSelfTrade") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SelfTrade)) ((:*:) (S1 (MetaSel (Just Symbol "noClientOid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ClientOrderId))) (S1 (MetaSel (Just Symbol "noSizeAndOrFunds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Size (Maybe Size, Cost)))))))) (C1 (MetaCons "NewStopOrder" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "noProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProductId)) ((:*:) (S1 (MetaSel (Just Symbol "noSide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Side)) (S1 (MetaSel (Just Symbol "noSelfTrade") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SelfTrade)))) ((:*:) (S1 (MetaSel (Just Symbol "noClientOid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ClientOrderId))) ((:*:) (S1 (MetaSel (Just Symbol "noPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Price)) (S1 (MetaSel (Just Symbol "noSizeAndOrFunds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Size (Maybe Size, Cost))))))))))

data OrderConfirmation Source #

Constructors

OrderConfirmation 

Fields

Instances

Data OrderConfirmation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderConfirmation -> c OrderConfirmation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderConfirmation #

toConstr :: OrderConfirmation -> Constr #

dataTypeOf :: OrderConfirmation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderConfirmation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderConfirmation) #

gmapT :: (forall b. Data b => b -> b) -> OrderConfirmation -> OrderConfirmation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderConfirmation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderConfirmation -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderConfirmation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderConfirmation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderConfirmation -> m OrderConfirmation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderConfirmation -> m OrderConfirmation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderConfirmation -> m OrderConfirmation #

Show OrderConfirmation Source # 
Generic OrderConfirmation Source # 
ToJSON OrderConfirmation Source # 
FromJSON OrderConfirmation Source # 
NFData OrderConfirmation Source # 

Methods

rnf :: OrderConfirmation -> () #

type Rep OrderConfirmation Source # 
type Rep OrderConfirmation = D1 (MetaData "OrderConfirmation" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "OrderConfirmation" PrefixI True) (S1 (MetaSel (Just Symbol "ocId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderId)))

data Order Source #

Instances

Data Order Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Order -> c Order #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Order #

toConstr :: Order -> Constr #

dataTypeOf :: Order -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Order) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Order) #

gmapT :: (forall b. Data b => b -> b) -> Order -> Order #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r #

gmapQ :: (forall d. Data d => d -> u) -> Order -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Order -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Order -> m Order #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order #

Show Order Source # 

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Generic Order Source # 

Associated Types

type Rep Order :: * -> * #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

ToJSON Order Source # 
FromJSON Order Source # 
NFData Order Source # 

Methods

rnf :: Order -> () #

type Rep Order Source # 
type Rep Order = D1 (MetaData "Order" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "LimitOrder" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderId)) (S1 (MetaSel (Just Symbol "orderProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProductId))) ((:*:) (S1 (MetaSel (Just Symbol "orderStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderStatus)) (S1 (MetaSel (Just Symbol "orderSelfTrade") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SelfTrade)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderSettled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "orderSide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Side))) ((:*:) (S1 (MetaSel (Just Symbol "orderCreatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) (S1 (MetaSel (Just Symbol "orderFilledSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Size)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderFilledFees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Price))) (S1 (MetaSel (Just Symbol "orderDoneAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime)))) ((:*:) (S1 (MetaSel (Just Symbol "orderDoneReason") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Reason))) (S1 (MetaSel (Just Symbol "orderPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Price)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size)) (S1 (MetaSel (Just Symbol "orderTimeInForce") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderContigency))) ((:*:) (S1 (MetaSel (Just Symbol "orderCancelAfter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OrderCancelAfter))) (S1 (MetaSel (Just Symbol "orderPostOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))))) ((:+:) (C1 (MetaCons "MarketOrder" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderId)) ((:*:) (S1 (MetaSel (Just Symbol "orderProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProductId)) (S1 (MetaSel (Just Symbol "orderStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderStatus)))) ((:*:) (S1 (MetaSel (Just Symbol "orderSelfTrade") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SelfTrade)) ((:*:) (S1 (MetaSel (Just Symbol "orderSettled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "orderSide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Side))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderCreatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) ((:*:) (S1 (MetaSel (Just Symbol "orderFilledSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Size))) (S1 (MetaSel (Just Symbol "orderFilledFees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Price))))) ((:*:) (S1 (MetaSel (Just Symbol "orderDoneAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime))) ((:*:) (S1 (MetaSel (Just Symbol "orderDoneReason") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Reason))) (S1 (MetaSel (Just Symbol "orderSizeAndOrFunds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Size (Maybe Size, Cost))))))))) (C1 (MetaCons "StopOrder" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderId)) ((:*:) (S1 (MetaSel (Just Symbol "orderProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProductId)) (S1 (MetaSel (Just Symbol "orderStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OrderStatus)))) ((:*:) (S1 (MetaSel (Just Symbol "orderSelfTrade") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SelfTrade)) ((:*:) (S1 (MetaSel (Just Symbol "orderSettled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "orderSide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Side))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderCreatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) ((:*:) (S1 (MetaSel (Just Symbol "orderFilledSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Size))) (S1 (MetaSel (Just Symbol "orderFilledFees") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Price))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "orderDoneAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime))) (S1 (MetaSel (Just Symbol "orderDoneReason") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Reason)))) ((:*:) (S1 (MetaSel (Just Symbol "orderPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Price)) (S1 (MetaSel (Just Symbol "orderSizeAndOrFunds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Size (Maybe Size, Cost)))))))))))

data Liquidity Source #

Constructors

Maker 
Taker 

Instances

Eq Liquidity Source # 
Data Liquidity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Liquidity -> c Liquidity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Liquidity #

toConstr :: Liquidity -> Constr #

dataTypeOf :: Liquidity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Liquidity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Liquidity) #

gmapT :: (forall b. Data b => b -> b) -> Liquidity -> Liquidity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Liquidity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Liquidity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Liquidity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Liquidity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Liquidity -> m Liquidity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Liquidity -> m Liquidity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Liquidity -> m Liquidity #

Ord Liquidity Source # 
Read Liquidity Source # 
Show Liquidity Source # 
Generic Liquidity Source # 

Associated Types

type Rep Liquidity :: * -> * #

Hashable Liquidity Source # 
ToJSON Liquidity Source # 
FromJSON Liquidity Source # 
NFData Liquidity Source # 

Methods

rnf :: Liquidity -> () #

type Rep Liquidity Source # 
type Rep Liquidity = D1 (MetaData "Liquidity" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "Maker" PrefixI False) U1) (C1 (MetaCons "Taker" PrefixI False) U1))

data Fill Source #

Instances

Data Fill Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fill -> c Fill #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fill #

toConstr :: Fill -> Constr #

dataTypeOf :: Fill -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Fill) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fill) #

gmapT :: (forall b. Data b => b -> b) -> Fill -> Fill #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fill -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fill -> r #

gmapQ :: (forall d. Data d => d -> u) -> Fill -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Fill -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fill -> m Fill #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fill -> m Fill #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fill -> m Fill #

Show Fill Source # 

Methods

showsPrec :: Int -> Fill -> ShowS #

show :: Fill -> String #

showList :: [Fill] -> ShowS #

Generic Fill Source # 

Associated Types

type Rep Fill :: * -> * #

Methods

from :: Fill -> Rep Fill x #

to :: Rep Fill x -> Fill #

ToJSON Fill Source # 
FromJSON Fill Source # 
NFData Fill Source # 

Methods

rnf :: Fill -> () #

type Rep Fill Source # 

newtype TransferId Source #

Constructors

TransferId 

Fields

Instances

Eq TransferId Source # 
Data TransferId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransferId -> c TransferId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransferId #

toConstr :: TransferId -> Constr #

dataTypeOf :: TransferId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TransferId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransferId) #

gmapT :: (forall b. Data b => b -> b) -> TransferId -> TransferId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransferId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransferId -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransferId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransferId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransferId -> m TransferId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferId -> m TransferId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferId -> m TransferId #

Ord TransferId Source # 
Read TransferId Source # 
Show TransferId Source # 
Generic TransferId Source # 

Associated Types

type Rep TransferId :: * -> * #

ToJSON TransferId Source # 
FromJSON TransferId Source # 
NFData TransferId Source # 

Methods

rnf :: TransferId -> () #

type Rep TransferId Source # 
type Rep TransferId = D1 (MetaData "TransferId" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "TransferId" PrefixI True) (S1 (MetaSel (Just Symbol "unTransferId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

newtype CoinbaseAccountId Source #

Instances

Eq CoinbaseAccountId Source # 
Data CoinbaseAccountId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoinbaseAccountId -> c CoinbaseAccountId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoinbaseAccountId #

toConstr :: CoinbaseAccountId -> Constr #

dataTypeOf :: CoinbaseAccountId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CoinbaseAccountId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoinbaseAccountId) #

gmapT :: (forall b. Data b => b -> b) -> CoinbaseAccountId -> CoinbaseAccountId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoinbaseAccountId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoinbaseAccountId -> r #

gmapQ :: (forall d. Data d => d -> u) -> CoinbaseAccountId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CoinbaseAccountId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoinbaseAccountId -> m CoinbaseAccountId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoinbaseAccountId -> m CoinbaseAccountId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoinbaseAccountId -> m CoinbaseAccountId #

Ord CoinbaseAccountId Source # 
Read CoinbaseAccountId Source # 
Show CoinbaseAccountId Source # 
Generic CoinbaseAccountId Source # 
ToJSON CoinbaseAccountId Source # 
FromJSON CoinbaseAccountId Source # 
NFData CoinbaseAccountId Source # 

Methods

rnf :: CoinbaseAccountId -> () #

type Rep CoinbaseAccountId Source # 
type Rep CoinbaseAccountId = D1 (MetaData "CoinbaseAccountId" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "CoinbaseAccountId" PrefixI True) (S1 (MetaSel (Just Symbol "unCoinbaseAccountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data TransferToCoinbase Source #

Instances

Data TransferToCoinbase Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransferToCoinbase -> c TransferToCoinbase #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransferToCoinbase #

toConstr :: TransferToCoinbase -> Constr #

dataTypeOf :: TransferToCoinbase -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TransferToCoinbase) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransferToCoinbase) #

gmapT :: (forall b. Data b => b -> b) -> TransferToCoinbase -> TransferToCoinbase #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransferToCoinbase -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransferToCoinbase -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransferToCoinbase -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransferToCoinbase -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransferToCoinbase -> m TransferToCoinbase #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferToCoinbase -> m TransferToCoinbase #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferToCoinbase -> m TransferToCoinbase #

Show TransferToCoinbase Source # 
Generic TransferToCoinbase Source # 
ToJSON TransferToCoinbase Source # 
NFData TransferToCoinbase Source # 

Methods

rnf :: TransferToCoinbase -> () #

type Rep TransferToCoinbase Source # 
type Rep TransferToCoinbase = D1 (MetaData "TransferToCoinbase" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "Deposit" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "trAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size)) (S1 (MetaSel (Just Symbol "trCoinbaseAccountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinbaseAccountId)))) (C1 (MetaCons "Withdraw" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "trAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size)) (S1 (MetaSel (Just Symbol "trCoinbaseAccountId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinbaseAccountId)))))

data CryptoWithdrawal Source #

Instances

Data CryptoWithdrawal Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CryptoWithdrawal -> c CryptoWithdrawal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CryptoWithdrawal #

toConstr :: CryptoWithdrawal -> Constr #

dataTypeOf :: CryptoWithdrawal -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CryptoWithdrawal) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CryptoWithdrawal) #

gmapT :: (forall b. Data b => b -> b) -> CryptoWithdrawal -> CryptoWithdrawal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CryptoWithdrawal -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CryptoWithdrawal -> r #

gmapQ :: (forall d. Data d => d -> u) -> CryptoWithdrawal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CryptoWithdrawal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CryptoWithdrawal -> m CryptoWithdrawal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoWithdrawal -> m CryptoWithdrawal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoWithdrawal -> m CryptoWithdrawal #

Show CryptoWithdrawal Source # 
Generic CryptoWithdrawal Source # 
ToJSON CryptoWithdrawal Source # 
FromJSON CryptoWithdrawal Source # 
NFData CryptoWithdrawal Source # 

Methods

rnf :: CryptoWithdrawal -> () #

type Rep CryptoWithdrawal Source # 
type Rep CryptoWithdrawal = D1 (MetaData "CryptoWithdrawal" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "Withdrawal" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "wdAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size)) ((:*:) (S1 (MetaSel (Just Symbol "wdCurrency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurrencyId)) (S1 (MetaSel (Just Symbol "wdCryptoAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CryptoWallet)))))

data CryptoWithdrawalResp Source #

Instances

Eq CryptoWithdrawalResp Source # 
Show CryptoWithdrawalResp Source # 
Generic CryptoWithdrawalResp Source # 
ToJSON CryptoWithdrawalResp Source # 
FromJSON CryptoWithdrawalResp Source # 
NFData CryptoWithdrawalResp Source # 

Methods

rnf :: CryptoWithdrawalResp -> () #

type Rep CryptoWithdrawalResp Source # 
type Rep CryptoWithdrawalResp = D1 (MetaData "CryptoWithdrawalResp" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "WithdrawalResp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "wdrId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TransferId)) ((:*:) (S1 (MetaSel (Just Symbol "wdrAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size)) (S1 (MetaSel (Just Symbol "wdrCurrency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurrencyId)))))

data CryptoWallet Source #

Constructors

BTCWallet BitcoinWallet 

Instances

Data CryptoWallet Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CryptoWallet -> c CryptoWallet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CryptoWallet #

toConstr :: CryptoWallet -> Constr #

dataTypeOf :: CryptoWallet -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CryptoWallet) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CryptoWallet) #

gmapT :: (forall b. Data b => b -> b) -> CryptoWallet -> CryptoWallet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CryptoWallet -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CryptoWallet -> r #

gmapQ :: (forall d. Data d => d -> u) -> CryptoWallet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CryptoWallet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CryptoWallet -> m CryptoWallet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoWallet -> m CryptoWallet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoWallet -> m CryptoWallet #

Show CryptoWallet Source # 
Generic CryptoWallet Source # 

Associated Types

type Rep CryptoWallet :: * -> * #

ToJSON CryptoWallet Source # 
FromJSON CryptoWallet Source # 
NFData CryptoWallet Source # 

Methods

rnf :: CryptoWallet -> () #

type Rep CryptoWallet Source # 
type Rep CryptoWallet = D1 (MetaData "CryptoWallet" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "BTCWallet" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BitcoinWallet)))

newtype BitcoinWallet Source #

Constructors

FromBTCAddress 

Fields

Instances

Data BitcoinWallet Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitcoinWallet -> c BitcoinWallet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitcoinWallet #

toConstr :: BitcoinWallet -> Constr #

dataTypeOf :: BitcoinWallet -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BitcoinWallet) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitcoinWallet) #

gmapT :: (forall b. Data b => b -> b) -> BitcoinWallet -> BitcoinWallet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitcoinWallet -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitcoinWallet -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitcoinWallet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitcoinWallet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitcoinWallet -> m BitcoinWallet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitcoinWallet -> m BitcoinWallet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitcoinWallet -> m BitcoinWallet #

Show BitcoinWallet Source # 
Generic BitcoinWallet Source # 

Associated Types

type Rep BitcoinWallet :: * -> * #

ToJSON BitcoinWallet Source # 
FromJSON BitcoinWallet Source # 
NFData BitcoinWallet Source # 

Methods

rnf :: BitcoinWallet -> () #

type Rep BitcoinWallet Source # 
type Rep BitcoinWallet = D1 (MetaData "BitcoinWallet" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "FromBTCAddress" PrefixI True) (S1 (MetaSel (Just Symbol "btcAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data BTCTransferReq Source #

Instances

Data BTCTransferReq Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BTCTransferReq -> c BTCTransferReq #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BTCTransferReq #

toConstr :: BTCTransferReq -> Constr #

dataTypeOf :: BTCTransferReq -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BTCTransferReq) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BTCTransferReq) #

gmapT :: (forall b. Data b => b -> b) -> BTCTransferReq -> BTCTransferReq #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BTCTransferReq -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BTCTransferReq -> r #

gmapQ :: (forall d. Data d => d -> u) -> BTCTransferReq -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BTCTransferReq -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BTCTransferReq -> m BTCTransferReq #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BTCTransferReq -> m BTCTransferReq #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BTCTransferReq -> m BTCTransferReq #

Show BTCTransferReq Source # 
Generic BTCTransferReq Source # 

Associated Types

type Rep BTCTransferReq :: * -> * #

ToJSON BTCTransferReq Source # 
NFData BTCTransferReq Source # 

Methods

rnf :: BTCTransferReq -> () #

type Rep BTCTransferReq Source # 
type Rep BTCTransferReq = D1 (MetaData "BTCTransferReq" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "SendBitcoin" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "sendAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size)) (S1 (MetaSel (Just Symbol "bitcoinWallet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BitcoinWallet))))

newtype BTCTransferId Source #

Constructors

BTCTransferId 

Instances

Eq BTCTransferId Source # 
Data BTCTransferId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BTCTransferId -> c BTCTransferId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BTCTransferId #

toConstr :: BTCTransferId -> Constr #

dataTypeOf :: BTCTransferId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BTCTransferId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BTCTransferId) #

gmapT :: (forall b. Data b => b -> b) -> BTCTransferId -> BTCTransferId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BTCTransferId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BTCTransferId -> r #

gmapQ :: (forall d. Data d => d -> u) -> BTCTransferId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BTCTransferId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BTCTransferId -> m BTCTransferId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BTCTransferId -> m BTCTransferId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BTCTransferId -> m BTCTransferId #

Ord BTCTransferId Source # 
Read BTCTransferId Source # 
Show BTCTransferId Source # 
Generic BTCTransferId Source # 

Associated Types

type Rep BTCTransferId :: * -> * #

ToJSON BTCTransferId Source # 
FromJSON BTCTransferId Source # 
NFData BTCTransferId Source # 

Methods

rnf :: BTCTransferId -> () #

type Rep BTCTransferId Source # 
type Rep BTCTransferId = D1 (MetaData "BTCTransferId" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "BTCTransferId" PrefixI True) (S1 (MetaSel (Just Symbol "getBtcTransferId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data BTCTransferResponse Source #

Constructors

BTCTransferResponse 

Instances

Eq BTCTransferResponse Source # 
Data BTCTransferResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BTCTransferResponse -> c BTCTransferResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BTCTransferResponse #

toConstr :: BTCTransferResponse -> Constr #

dataTypeOf :: BTCTransferResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BTCTransferResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BTCTransferResponse) #

gmapT :: (forall b. Data b => b -> b) -> BTCTransferResponse -> BTCTransferResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BTCTransferResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BTCTransferResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> BTCTransferResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BTCTransferResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BTCTransferResponse -> m BTCTransferResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BTCTransferResponse -> m BTCTransferResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BTCTransferResponse -> m BTCTransferResponse #

Show BTCTransferResponse Source # 
Generic BTCTransferResponse Source # 
FromJSON BTCTransferResponse Source # 
NFData BTCTransferResponse Source # 

Methods

rnf :: BTCTransferResponse -> () #

type Rep BTCTransferResponse Source # 
type Rep BTCTransferResponse = D1 (MetaData "BTCTransferResponse" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "BTCTransferResponse" PrefixI True) (S1 (MetaSel (Just Symbol "sendId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BTCTransferId)))

data CoinbaseAccount Source #

Instances

Data CoinbaseAccount Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoinbaseAccount -> c CoinbaseAccount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoinbaseAccount #

toConstr :: CoinbaseAccount -> Constr #

dataTypeOf :: CoinbaseAccount -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CoinbaseAccount) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoinbaseAccount) #

gmapT :: (forall b. Data b => b -> b) -> CoinbaseAccount -> CoinbaseAccount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoinbaseAccount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoinbaseAccount -> r #

gmapQ :: (forall d. Data d => d -> u) -> CoinbaseAccount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CoinbaseAccount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoinbaseAccount -> m CoinbaseAccount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoinbaseAccount -> m CoinbaseAccount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoinbaseAccount -> m CoinbaseAccount #

Show CoinbaseAccount Source # 
Generic CoinbaseAccount Source # 
FromJSON CoinbaseAccount Source # 
type Rep CoinbaseAccount Source # 

newtype ReportId Source #

Constructors

ReportId 

Fields

Instances

Eq ReportId Source # 
Data ReportId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportId -> c ReportId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportId #

toConstr :: ReportId -> Constr #

dataTypeOf :: ReportId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportId) #

gmapT :: (forall b. Data b => b -> b) -> ReportId -> ReportId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportId -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportId -> m ReportId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportId -> m ReportId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportId -> m ReportId #

Ord ReportId Source # 
Read ReportId Source # 
Show ReportId Source # 
Generic ReportId Source # 

Associated Types

type Rep ReportId :: * -> * #

Methods

from :: ReportId -> Rep ReportId x #

to :: Rep ReportId x -> ReportId #

ToJSON ReportId Source # 
FromJSON ReportId Source # 
NFData ReportId Source # 

Methods

rnf :: ReportId -> () #

type Rep ReportId Source # 
type Rep ReportId = D1 (MetaData "ReportId" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "ReportId" PrefixI True) (S1 (MetaSel (Just Symbol "unReportId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data ReportType Source #

Constructors

FillsReport 
AccountReport 

Instances

Eq ReportType Source # 
Data ReportType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportType -> c ReportType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportType #

toConstr :: ReportType -> Constr #

dataTypeOf :: ReportType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportType) #

gmapT :: (forall b. Data b => b -> b) -> ReportType -> ReportType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportType -> m ReportType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportType -> m ReportType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportType -> m ReportType #

Ord ReportType Source # 
Read ReportType Source # 
Show ReportType Source # 
Generic ReportType Source # 

Associated Types

type Rep ReportType :: * -> * #

Hashable ReportType Source # 
ToJSON ReportType Source # 
FromJSON ReportType Source # 
NFData ReportType Source # 

Methods

rnf :: ReportType -> () #

type Rep ReportType Source # 
type Rep ReportType = D1 (MetaData "ReportType" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "FillsReport" PrefixI False) U1) (C1 (MetaCons "AccountReport" PrefixI False) U1))

data ReportFormat Source #

Constructors

PDF 
CSV 

Instances

Eq ReportFormat Source # 
Data ReportFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportFormat -> c ReportFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportFormat #

toConstr :: ReportFormat -> Constr #

dataTypeOf :: ReportFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportFormat) #

gmapT :: (forall b. Data b => b -> b) -> ReportFormat -> ReportFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportFormat -> m ReportFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportFormat -> m ReportFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportFormat -> m ReportFormat #

Ord ReportFormat Source # 
Read ReportFormat Source # 
Show ReportFormat Source # 
Generic ReportFormat Source # 

Associated Types

type Rep ReportFormat :: * -> * #

Hashable ReportFormat Source # 
ToJSON ReportFormat Source # 
FromJSON ReportFormat Source # 
NFData ReportFormat Source # 

Methods

rnf :: ReportFormat -> () #

type Rep ReportFormat Source # 
type Rep ReportFormat = D1 (MetaData "ReportFormat" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "PDF" PrefixI False) U1) (C1 (MetaCons "CSV" PrefixI False) U1))

data ReportRequest Source #

Instances

Data ReportRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportRequest -> c ReportRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportRequest #

toConstr :: ReportRequest -> Constr #

dataTypeOf :: ReportRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportRequest) #

gmapT :: (forall b. Data b => b -> b) -> ReportRequest -> ReportRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportRequest -> m ReportRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportRequest -> m ReportRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportRequest -> m ReportRequest #

Show ReportRequest Source # 
Generic ReportRequest Source # 

Associated Types

type Rep ReportRequest :: * -> * #

ToJSON ReportRequest Source # 
FromJSON ReportRequest Source # 
NFData ReportRequest Source # 

Methods

rnf :: ReportRequest -> () #

type Rep ReportRequest Source # 

data ReportParams Source #

Instances

Data ReportParams Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportParams -> c ReportParams #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportParams #

toConstr :: ReportParams -> Constr #

dataTypeOf :: ReportParams -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportParams) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportParams) #

gmapT :: (forall b. Data b => b -> b) -> ReportParams -> ReportParams #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportParams -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportParams -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportParams -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportParams -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportParams -> m ReportParams #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportParams -> m ReportParams #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportParams -> m ReportParams #

Show ReportParams Source # 
Generic ReportParams Source # 

Associated Types

type Rep ReportParams :: * -> * #

ToJSON ReportParams Source # 
FromJSON ReportParams Source # 
NFData ReportParams Source # 

Methods

rnf :: ReportParams -> () #

type Rep ReportParams Source # 
type Rep ReportParams = D1 (MetaData "ReportParams" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "ReportParams" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "reportStartDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) (S1 (MetaSel (Just Symbol "reportEndDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime))))

data ReportStatus Source #

Instances

Eq ReportStatus Source # 
Data ReportStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportStatus -> c ReportStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportStatus #

toConstr :: ReportStatus -> Constr #

dataTypeOf :: ReportStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportStatus) #

gmapT :: (forall b. Data b => b -> b) -> ReportStatus -> ReportStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportStatus -> m ReportStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportStatus -> m ReportStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportStatus -> m ReportStatus #

Ord ReportStatus Source # 
Read ReportStatus Source # 
Show ReportStatus Source # 
Generic ReportStatus Source # 

Associated Types

type Rep ReportStatus :: * -> * #

Hashable ReportStatus Source # 
ToJSON ReportStatus Source # 
FromJSON ReportStatus Source # 
NFData ReportStatus Source # 

Methods

rnf :: ReportStatus -> () #

type Rep ReportStatus Source # 
type Rep ReportStatus = D1 (MetaData "ReportStatus" "Coinbase.Exchange.Types.Private" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "ReportPending" PrefixI False) U1) ((:+:) (C1 (MetaCons "ReportCreating" PrefixI False) U1) (C1 (MetaCons "ReportReady" PrefixI False) U1)))

data ReportInfo Source #

Instances

Data ReportInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportInfo -> c ReportInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportInfo #

toConstr :: ReportInfo -> Constr #

dataTypeOf :: ReportInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportInfo) #

gmapT :: (forall b. Data b => b -> b) -> ReportInfo -> ReportInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportInfo -> m ReportInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportInfo -> m ReportInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportInfo -> m ReportInfo #

Show ReportInfo Source # 
Generic ReportInfo Source # 

Associated Types

type Rep ReportInfo :: * -> * #

ToJSON ReportInfo Source # 
FromJSON ReportInfo Source # 
NFData ReportInfo Source # 

Methods

rnf :: ReportInfo -> () #

type Rep ReportInfo Source #