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

Safe HaskellNone
LanguageHaskell2010

Coinbase.Exchange.Types.Core

Documentation

newtype ProductId Source #

Constructors

ProductId 

Fields

Instances

Eq ProductId Source # 
Data ProductId Source # 

Methods

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

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

toConstr :: ProductId -> Constr #

dataTypeOf :: ProductId -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ProductId -> () #

type Rep ProductId Source # 
type Rep ProductId = D1 (MetaData "ProductId" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "ProductId" PrefixI True) (S1 (MetaSel (Just Symbol "unProductId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Price Source #

Constructors

Price 

Instances

Eq Price Source # 

Methods

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

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

Fractional Price Source # 
Data Price Source # 

Methods

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

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

toConstr :: Price -> Constr #

dataTypeOf :: Price -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Price Source # 
Ord Price Source # 

Methods

compare :: Price -> Price -> Ordering #

(<) :: Price -> Price -> Bool #

(<=) :: Price -> Price -> Bool #

(>) :: Price -> Price -> Bool #

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

max :: Price -> Price -> Price #

min :: Price -> Price -> Price #

Read Price Source # 
Real Price Source # 

Methods

toRational :: Price -> Rational #

RealFrac Price Source # 

Methods

properFraction :: Integral b => Price -> (b, Price) #

truncate :: Integral b => Price -> b #

round :: Integral b => Price -> b #

ceiling :: Integral b => Price -> b #

floor :: Integral b => Price -> b #

Show Price Source # 

Methods

showsPrec :: Int -> Price -> ShowS #

show :: Price -> String #

showList :: [Price] -> ShowS #

Generic Price Source # 

Associated Types

type Rep Price :: * -> * #

Methods

from :: Price -> Rep Price x #

to :: Rep Price x -> Price #

Hashable Price Source # 

Methods

hashWithSalt :: Int -> Price -> Int #

hash :: Price -> Int #

ToJSON Price Source # 
FromJSON Price Source # 
NFData Price Source # 

Methods

rnf :: Price -> () #

type Rep Price Source # 
type Rep Price = D1 (MetaData "Price" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Price" PrefixI True) (S1 (MetaSel (Just Symbol "unPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinScientific)))

newtype Size Source #

Constructors

Size 

Instances

Eq Size Source # 

Methods

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

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

Fractional Size Source # 

Methods

(/) :: Size -> Size -> Size #

recip :: Size -> Size #

fromRational :: Rational -> Size #

Data Size Source # 

Methods

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

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

toConstr :: Size -> Constr #

dataTypeOf :: Size -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Size Source # 

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

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

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Read Size Source # 
Real Size Source # 

Methods

toRational :: Size -> Rational #

RealFrac Size Source # 

Methods

properFraction :: Integral b => Size -> (b, Size) #

truncate :: Integral b => Size -> b #

round :: Integral b => Size -> b #

ceiling :: Integral b => Size -> b #

floor :: Integral b => Size -> b #

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Generic Size Source # 

Associated Types

type Rep Size :: * -> * #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

Hashable Size Source # 

Methods

hashWithSalt :: Int -> Size -> Int #

hash :: Size -> Int #

ToJSON Size Source # 
FromJSON Size Source # 
NFData Size Source # 

Methods

rnf :: Size -> () #

type Rep Size Source # 
type Rep Size = D1 (MetaData "Size" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Size" PrefixI True) (S1 (MetaSel (Just Symbol "unSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinScientific)))

newtype Cost Source #

Constructors

Cost 

Instances

Eq Cost Source # 

Methods

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

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

Fractional Cost Source # 

Methods

(/) :: Cost -> Cost -> Cost #

recip :: Cost -> Cost #

fromRational :: Rational -> Cost #

Data Cost Source # 

Methods

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

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

toConstr :: Cost -> Constr #

dataTypeOf :: Cost -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Cost Source # 

Methods

(+) :: Cost -> Cost -> Cost #

(-) :: Cost -> Cost -> Cost #

(*) :: Cost -> Cost -> Cost #

negate :: Cost -> Cost #

abs :: Cost -> Cost #

signum :: Cost -> Cost #

fromInteger :: Integer -> Cost #

Ord Cost Source # 

Methods

compare :: Cost -> Cost -> Ordering #

(<) :: Cost -> Cost -> Bool #

(<=) :: Cost -> Cost -> Bool #

(>) :: Cost -> Cost -> Bool #

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

max :: Cost -> Cost -> Cost #

min :: Cost -> Cost -> Cost #

Read Cost Source # 
Real Cost Source # 

Methods

toRational :: Cost -> Rational #

RealFrac Cost Source # 

Methods

properFraction :: Integral b => Cost -> (b, Cost) #

truncate :: Integral b => Cost -> b #

round :: Integral b => Cost -> b #

ceiling :: Integral b => Cost -> b #

floor :: Integral b => Cost -> b #

Show Cost Source # 

Methods

showsPrec :: Int -> Cost -> ShowS #

show :: Cost -> String #

showList :: [Cost] -> ShowS #

Generic Cost Source # 

Associated Types

type Rep Cost :: * -> * #

Methods

from :: Cost -> Rep Cost x #

to :: Rep Cost x -> Cost #

Hashable Cost Source # 

Methods

hashWithSalt :: Int -> Cost -> Int #

hash :: Cost -> Int #

ToJSON Cost Source # 
FromJSON Cost Source # 
NFData Cost Source # 

Methods

rnf :: Cost -> () #

type Rep Cost Source # 
type Rep Cost = D1 (MetaData "Cost" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Cost" PrefixI True) (S1 (MetaSel (Just Symbol "unCost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinScientific)))

newtype OrderId Source #

Constructors

OrderId 

Fields

Instances

Eq OrderId Source # 

Methods

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

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

Data OrderId Source # 

Methods

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

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

toConstr :: OrderId -> Constr #

dataTypeOf :: OrderId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrderId Source # 
Read OrderId Source # 
Show OrderId Source # 
Generic OrderId Source # 

Associated Types

type Rep OrderId :: * -> * #

Methods

from :: OrderId -> Rep OrderId x #

to :: Rep OrderId x -> OrderId #

Hashable OrderId Source # 

Methods

hashWithSalt :: Int -> OrderId -> Int #

hash :: OrderId -> Int #

ToJSON OrderId Source # 
FromJSON OrderId Source # 
NFData OrderId Source # 

Methods

rnf :: OrderId -> () #

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

newtype Aggregate Source #

Constructors

Aggregate 

Fields

Instances

Eq Aggregate Source # 
Data Aggregate Source # 

Methods

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

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

toConstr :: Aggregate -> Constr #

dataTypeOf :: Aggregate -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Aggregate Source # 
Ord Aggregate Source # 
Read Aggregate Source # 
Show Aggregate Source # 
Generic Aggregate Source # 

Associated Types

type Rep Aggregate :: * -> * #

Hashable Aggregate Source # 
ToJSON Aggregate Source # 
FromJSON Aggregate Source # 
NFData Aggregate Source # 

Methods

rnf :: Aggregate -> () #

type Rep Aggregate Source # 
type Rep Aggregate = D1 (MetaData "Aggregate" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Aggregate" PrefixI True) (S1 (MetaSel (Just Symbol "unAggregate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

newtype Sequence Source #

Constructors

Sequence 

Fields

Instances

Enum Sequence Source # 
Eq Sequence Source # 
Data Sequence Source # 

Methods

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

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

toConstr :: Sequence -> Constr #

dataTypeOf :: Sequence -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: Sequence -> () #

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

data Side Source #

Constructors

Buy 
Sell 

Instances

Eq Side Source # 

Methods

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

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

Data Side Source # 

Methods

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

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

toConstr :: Side -> Constr #

dataTypeOf :: Side -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Side Source # 

Methods

compare :: Side -> Side -> Ordering #

(<) :: Side -> Side -> Bool #

(<=) :: Side -> Side -> Bool #

(>) :: Side -> Side -> Bool #

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

max :: Side -> Side -> Side #

min :: Side -> Side -> Side #

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

Methods

rnf :: Side -> () #

type Rep Side Source # 
type Rep Side = D1 (MetaData "Side" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "Buy" PrefixI False) U1) (C1 (MetaCons "Sell" PrefixI False) U1))

data OrderType Source #

Constructors

Limit 
Market 

Instances

Eq OrderType Source # 
Data OrderType Source # 

Methods

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

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

toConstr :: OrderType -> Constr #

dataTypeOf :: OrderType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrderType Source # 
Read OrderType Source # 
Show OrderType Source # 
Generic OrderType Source # 

Associated Types

type Rep OrderType :: * -> * #

Hashable OrderType Source # 
ToJSON OrderType Source # 
FromJSON OrderType Source # 
NFData OrderType Source # 

Methods

rnf :: OrderType -> () #

type Rep OrderType Source # 
type Rep OrderType = D1 (MetaData "OrderType" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "Limit" PrefixI False) U1) (C1 (MetaCons "Market" PrefixI False) U1))

newtype TradeId Source #

Constructors

TradeId 

Fields

Instances

Eq TradeId Source # 

Methods

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

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

Data TradeId Source # 

Methods

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

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

toConstr :: TradeId -> Constr #

dataTypeOf :: TradeId -> DataType #

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

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

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

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

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

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

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

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

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

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

Num TradeId Source # 
Ord TradeId Source # 
Read TradeId Source # 
Show TradeId Source # 
Generic TradeId Source # 

Associated Types

type Rep TradeId :: * -> * #

Methods

from :: TradeId -> Rep TradeId x #

to :: Rep TradeId x -> TradeId #

Hashable TradeId Source # 

Methods

hashWithSalt :: Int -> TradeId -> Int #

hash :: TradeId -> Int #

ToJSON TradeId Source # 
FromJSON TradeId Source # 
NFData TradeId Source # 

Methods

rnf :: TradeId -> () #

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

newtype CurrencyId Source #

Constructors

CurrencyId 

Fields

Instances

Eq CurrencyId Source # 
Data CurrencyId Source # 

Methods

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

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

toConstr :: CurrencyId -> Constr #

dataTypeOf :: CurrencyId -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: CurrencyId -> () #

type Rep CurrencyId Source # 
type Rep CurrencyId = D1 (MetaData "CurrencyId" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "CurrencyId" PrefixI True) (S1 (MetaSel (Just Symbol "unCurrencyId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data OrderStatus Source #

Constructors

Done 
Settled 
Open 
Pending 
Active 

Instances

Eq OrderStatus Source # 
Data OrderStatus Source # 

Methods

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

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

toConstr :: OrderStatus -> Constr #

dataTypeOf :: OrderStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OrderStatus Source # 
Show OrderStatus Source # 
Generic OrderStatus Source # 

Associated Types

type Rep OrderStatus :: * -> * #

Hashable OrderStatus Source # 
ToJSON OrderStatus Source # 
FromJSON OrderStatus Source # 
NFData OrderStatus Source # 

Methods

rnf :: OrderStatus -> () #

type Rep OrderStatus Source # 
type Rep OrderStatus = D1 (MetaData "OrderStatus" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) ((:+:) (C1 (MetaCons "Done" PrefixI False) U1) (C1 (MetaCons "Settled" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Open" PrefixI False) U1) ((:+:) (C1 (MetaCons "Pending" PrefixI False) U1) (C1 (MetaCons "Active" PrefixI False) U1))))

newtype ClientOrderId Source #

Constructors

ClientOrderId 

Instances

Eq ClientOrderId Source # 
Data ClientOrderId Source # 

Methods

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

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

toConstr :: ClientOrderId -> Constr #

dataTypeOf :: ClientOrderId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClientOrderId Source # 
Read ClientOrderId Source # 
Show ClientOrderId Source # 
Generic ClientOrderId Source # 

Associated Types

type Rep ClientOrderId :: * -> * #

Hashable ClientOrderId Source # 
ToJSON ClientOrderId Source # 
FromJSON ClientOrderId Source # 
NFData ClientOrderId Source # 

Methods

rnf :: ClientOrderId -> () #

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

data Reason Source #

Constructors

Filled 
Canceled 

Instances

Eq Reason Source # 

Methods

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

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

Data Reason Source # 

Methods

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

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

toConstr :: Reason -> Constr #

dataTypeOf :: Reason -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Reason Source # 
Show Reason Source # 
Generic Reason Source # 

Associated Types

type Rep Reason :: * -> * #

Methods

from :: Reason -> Rep Reason x #

to :: Rep Reason x -> Reason #

Hashable Reason Source # 

Methods

hashWithSalt :: Int -> Reason -> Int #

hash :: Reason -> Int #

ToJSON Reason Source # 
FromJSON Reason Source # 
NFData Reason Source # 

Methods

rnf :: Reason -> () #

type Rep Reason Source # 
type Rep Reason = D1 (MetaData "Reason" "Coinbase.Exchange.Types.Core" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) ((:+:) (C1 (MetaCons "Filled" PrefixI False) U1) (C1 (MetaCons "Canceled" PrefixI False) U1))

newtype CoinScientific Source #

Instances

Eq CoinScientific Source # 
Fractional CoinScientific Source # 
Data CoinScientific Source # 

Methods

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

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

toConstr :: CoinScientific -> Constr #

dataTypeOf :: CoinScientific -> DataType #

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

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

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

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

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

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

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

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

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

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

Num CoinScientific Source # 
Ord CoinScientific Source # 
Read CoinScientific Source # 
Real CoinScientific Source # 
RealFrac CoinScientific Source # 
Show CoinScientific Source # 
Hashable CoinScientific Source # 
ToJSON CoinScientific Source # 
FromJSON CoinScientific Source # 
NFData CoinScientific Source # 

Methods

rnf :: CoinScientific -> () #