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

Safe HaskellNone
LanguageHaskell2010

Coinbase.Exchange.Types.MarketData

Documentation

data Product Source #

Instances

Data Product Source # 

Methods

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

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

toConstr :: Product -> Constr #

dataTypeOf :: Product -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Product Source # 
Generic Product Source # 

Associated Types

type Rep Product :: * -> * #

Methods

from :: Product -> Rep Product x #

to :: Rep Product x -> Product #

ToJSON Product Source # 
FromJSON Product Source # 
NFData Product Source # 

Methods

rnf :: Product -> () #

type Rep Product Source # 

data Book a Source #

Constructors

Book 

Instances

Data a => Data (Book a) Source # 

Methods

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

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

toConstr :: Book a -> Constr #

dataTypeOf :: Book a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (Book a) Source # 

Methods

showsPrec :: Int -> Book a -> ShowS #

show :: Book a -> String #

showList :: [Book a] -> ShowS #

Generic (Book a) Source # 

Associated Types

type Rep (Book a) :: * -> * #

Methods

from :: Book a -> Rep (Book a) x #

to :: Rep (Book a) x -> Book a #

ToJSON a => ToJSON (Book a) Source # 
FromJSON a => FromJSON (Book a) Source # 
NFData a => NFData (Book a) Source # 

Methods

rnf :: Book a -> () #

type Rep (Book a) Source # 
type Rep (Book a) = D1 (MetaData "Book" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "Book" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "bookSequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Sequence)) ((:*:) (S1 (MetaSel (Just Symbol "bookBids") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [BookItem a])) (S1 (MetaSel (Just Symbol "bookAsks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [BookItem a])))))

data BookItem a Source #

Constructors

BookItem Price Size a 

Instances

Eq a => Eq (BookItem a) Source # 

Methods

(==) :: BookItem a -> BookItem a -> Bool #

(/=) :: BookItem a -> BookItem a -> Bool #

Data a => Data (BookItem a) Source # 

Methods

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

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

toConstr :: BookItem a -> Constr #

dataTypeOf :: BookItem a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (BookItem a) Source # 

Methods

compare :: BookItem a -> BookItem a -> Ordering #

(<) :: BookItem a -> BookItem a -> Bool #

(<=) :: BookItem a -> BookItem a -> Bool #

(>) :: BookItem a -> BookItem a -> Bool #

(>=) :: BookItem a -> BookItem a -> Bool #

max :: BookItem a -> BookItem a -> BookItem a #

min :: BookItem a -> BookItem a -> BookItem a #

Read a => Read (BookItem a) Source # 
Show a => Show (BookItem a) Source # 

Methods

showsPrec :: Int -> BookItem a -> ShowS #

show :: BookItem a -> String #

showList :: [BookItem a] -> ShowS #

Generic (BookItem a) Source # 

Associated Types

type Rep (BookItem a) :: * -> * #

Methods

from :: BookItem a -> Rep (BookItem a) x #

to :: Rep (BookItem a) x -> BookItem a #

ToJSON a => ToJSON (BookItem a) Source # 
FromJSON a => FromJSON (BookItem a) Source # 
NFData a => NFData (BookItem a) Source # 

Methods

rnf :: BookItem a -> () #

type Rep (BookItem a) Source # 

data Tick Source #

Constructors

Tick 

Instances

Data Tick Source # 

Methods

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

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

toConstr :: Tick -> Constr #

dataTypeOf :: Tick -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Tick Source # 

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

Generic Tick Source # 

Associated Types

type Rep Tick :: * -> * #

Methods

from :: Tick -> Rep Tick x #

to :: Rep Tick x -> Tick #

ToJSON Tick Source # 
FromJSON Tick Source # 
NFData Tick Source # 

Methods

rnf :: Tick -> () #

type Rep Tick Source # 
type Rep Tick = D1 (MetaData "Tick" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "Tick" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tickTradeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "tickPrice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Price))) ((:*:) (S1 (MetaSel (Just Symbol "tickSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Size)) (S1 (MetaSel (Just Symbol "tickTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime))))))

data Trade Source #

Instances

Data Trade Source # 

Methods

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

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

toConstr :: Trade -> Constr #

dataTypeOf :: Trade -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Trade Source # 

Methods

showsPrec :: Int -> Trade -> ShowS #

show :: Trade -> String #

showList :: [Trade] -> ShowS #

Generic Trade Source # 

Associated Types

type Rep Trade :: * -> * #

Methods

from :: Trade -> Rep Trade x #

to :: Rep Trade x -> Trade #

ToJSON Trade Source # 
FromJSON Trade Source # 
NFData Trade Source # 

Methods

rnf :: Trade -> () #

type Rep Trade Source # 

data Candle Source #

Instances

Data Candle Source # 

Methods

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

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

toConstr :: Candle -> Constr #

dataTypeOf :: Candle -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Candle Source # 
Generic Candle Source # 

Associated Types

type Rep Candle :: * -> * #

Methods

from :: Candle -> Rep Candle x #

to :: Rep Candle x -> Candle #

FromJSON Candle Source # 
NFData Candle Source # 

Methods

rnf :: Candle -> () #

type Rep Candle Source # 

newtype Low Source #

Constructors

Low 

Fields

Instances

Eq Low Source # 

Methods

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

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

Fractional Low Source # 

Methods

(/) :: Low -> Low -> Low #

recip :: Low -> Low #

fromRational :: Rational -> Low #

Data Low Source # 

Methods

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

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

toConstr :: Low -> Constr #

dataTypeOf :: Low -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Low Source # 

Methods

(+) :: Low -> Low -> Low #

(-) :: Low -> Low -> Low #

(*) :: Low -> Low -> Low #

negate :: Low -> Low #

abs :: Low -> Low #

signum :: Low -> Low #

fromInteger :: Integer -> Low #

Ord Low Source # 

Methods

compare :: Low -> Low -> Ordering #

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

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

(>) :: Low -> Low -> Bool #

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

max :: Low -> Low -> Low #

min :: Low -> Low -> Low #

Read Low Source # 
Real Low Source # 

Methods

toRational :: Low -> Rational #

RealFrac Low Source # 

Methods

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

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

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

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

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

Show Low Source # 

Methods

showsPrec :: Int -> Low -> ShowS #

show :: Low -> String #

showList :: [Low] -> ShowS #

Generic Low Source # 

Associated Types

type Rep Low :: * -> * #

Methods

from :: Low -> Rep Low x #

to :: Rep Low x -> Low #

Hashable Low Source # 

Methods

hashWithSalt :: Int -> Low -> Int #

hash :: Low -> Int #

ToJSON Low Source # 
FromJSON Low Source # 
NFData Low Source # 

Methods

rnf :: Low -> () #

type Rep Low Source # 
type Rep Low = D1 (MetaData "Low" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Low" PrefixI True) (S1 (MetaSel (Just Symbol "unLow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))

newtype High Source #

Constructors

High 

Fields

Instances

Eq High Source # 

Methods

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

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

Fractional High Source # 

Methods

(/) :: High -> High -> High #

recip :: High -> High #

fromRational :: Rational -> High #

Data High Source # 

Methods

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

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

toConstr :: High -> Constr #

dataTypeOf :: High -> DataType #

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

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

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

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

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

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

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

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

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

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

Num High Source # 

Methods

(+) :: High -> High -> High #

(-) :: High -> High -> High #

(*) :: High -> High -> High #

negate :: High -> High #

abs :: High -> High #

signum :: High -> High #

fromInteger :: Integer -> High #

Ord High Source # 

Methods

compare :: High -> High -> Ordering #

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

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

(>) :: High -> High -> Bool #

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

max :: High -> High -> High #

min :: High -> High -> High #

Read High Source # 
Real High Source # 

Methods

toRational :: High -> Rational #

RealFrac High Source # 

Methods

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

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

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

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

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

Show High Source # 

Methods

showsPrec :: Int -> High -> ShowS #

show :: High -> String #

showList :: [High] -> ShowS #

Generic High Source # 

Associated Types

type Rep High :: * -> * #

Methods

from :: High -> Rep High x #

to :: Rep High x -> High #

Hashable High Source # 

Methods

hashWithSalt :: Int -> High -> Int #

hash :: High -> Int #

ToJSON High Source # 
FromJSON High Source # 
NFData High Source # 

Methods

rnf :: High -> () #

type Rep High Source # 
type Rep High = D1 (MetaData "High" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "High" PrefixI True) (S1 (MetaSel (Just Symbol "unHigh") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))

newtype Open Source #

Constructors

Open 

Fields

Instances

Eq Open Source # 

Methods

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

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

Fractional Open Source # 

Methods

(/) :: Open -> Open -> Open #

recip :: Open -> Open #

fromRational :: Rational -> Open #

Data Open Source # 

Methods

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

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

toConstr :: Open -> Constr #

dataTypeOf :: Open -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Open Source # 

Methods

(+) :: Open -> Open -> Open #

(-) :: Open -> Open -> Open #

(*) :: Open -> Open -> Open #

negate :: Open -> Open #

abs :: Open -> Open #

signum :: Open -> Open #

fromInteger :: Integer -> Open #

Ord Open Source # 

Methods

compare :: Open -> Open -> Ordering #

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

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

(>) :: Open -> Open -> Bool #

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

max :: Open -> Open -> Open #

min :: Open -> Open -> Open #

Read Open Source # 
Real Open Source # 

Methods

toRational :: Open -> Rational #

RealFrac Open Source # 

Methods

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

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

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

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

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

Show Open Source # 

Methods

showsPrec :: Int -> Open -> ShowS #

show :: Open -> String #

showList :: [Open] -> ShowS #

Generic Open Source # 

Associated Types

type Rep Open :: * -> * #

Methods

from :: Open -> Rep Open x #

to :: Rep Open x -> Open #

Hashable Open Source # 

Methods

hashWithSalt :: Int -> Open -> Int #

hash :: Open -> Int #

ToJSON Open Source # 
FromJSON Open Source # 
NFData Open Source # 

Methods

rnf :: Open -> () #

type Rep Open Source # 
type Rep Open = D1 (MetaData "Open" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Open" PrefixI True) (S1 (MetaSel (Just Symbol "unOpen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))

newtype Close Source #

Constructors

Close 

Fields

Instances

Eq Close Source # 

Methods

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

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

Fractional Close Source # 
Data Close Source # 

Methods

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

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

toConstr :: Close -> Constr #

dataTypeOf :: Close -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Close Source # 
Ord Close Source # 

Methods

compare :: Close -> Close -> Ordering #

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

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

(>) :: Close -> Close -> Bool #

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

max :: Close -> Close -> Close #

min :: Close -> Close -> Close #

Read Close Source # 
Real Close Source # 

Methods

toRational :: Close -> Rational #

RealFrac Close Source # 

Methods

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

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

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

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

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

Show Close Source # 

Methods

showsPrec :: Int -> Close -> ShowS #

show :: Close -> String #

showList :: [Close] -> ShowS #

Generic Close Source # 

Associated Types

type Rep Close :: * -> * #

Methods

from :: Close -> Rep Close x #

to :: Rep Close x -> Close #

Hashable Close Source # 

Methods

hashWithSalt :: Int -> Close -> Int #

hash :: Close -> Int #

ToJSON Close Source # 
FromJSON Close Source # 
NFData Close Source # 

Methods

rnf :: Close -> () #

type Rep Close Source # 
type Rep Close = D1 (MetaData "Close" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Close" PrefixI True) (S1 (MetaSel (Just Symbol "unClose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))

newtype Volume Source #

Constructors

Volume 

Fields

Instances

Eq Volume Source # 

Methods

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

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

Fractional Volume Source # 
Data Volume Source # 

Methods

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

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

toConstr :: Volume -> Constr #

dataTypeOf :: Volume -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Volume Source # 
Ord Volume Source # 
Read Volume Source # 
Real Volume Source # 
RealFrac Volume Source # 

Methods

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

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

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

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

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

Show Volume Source # 
Generic Volume Source # 

Associated Types

type Rep Volume :: * -> * #

Methods

from :: Volume -> Rep Volume x #

to :: Rep Volume x -> Volume #

Hashable Volume Source # 

Methods

hashWithSalt :: Int -> Volume -> Int #

hash :: Volume -> Int #

ToJSON Volume Source # 
FromJSON Volume Source # 
NFData Volume Source # 

Methods

rnf :: Volume -> () #

type Rep Volume Source # 
type Rep Volume = D1 (MetaData "Volume" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" True) (C1 (MetaCons "Volume" PrefixI True) (S1 (MetaSel (Just Symbol "unVolume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))

data Stats Source #

Constructors

Stats 

Instances

Data Stats Source # 

Methods

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

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

toConstr :: Stats -> Constr #

dataTypeOf :: Stats -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Stats Source # 

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

Generic Stats Source # 

Associated Types

type Rep Stats :: * -> * #

Methods

from :: Stats -> Rep Stats x #

to :: Rep Stats x -> Stats #

ToJSON Stats Source # 
FromJSON Stats Source # 
NFData Stats Source # 

Methods

rnf :: Stats -> () #

type Rep Stats Source # 
type Rep Stats = D1 (MetaData "Stats" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "Stats" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statsOpen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Open)) (S1 (MetaSel (Just Symbol "statsHigh") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 High))) ((:*:) (S1 (MetaSel (Just Symbol "statsLow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Low)) (S1 (MetaSel (Just Symbol "statsVolume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Volume)))))

data Currency Source #

Instances

Data Currency Source # 

Methods

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

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

toConstr :: Currency -> Constr #

dataTypeOf :: Currency -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Currency Source # 
Generic Currency Source # 

Associated Types

type Rep Currency :: * -> * #

Methods

from :: Currency -> Rep Currency x #

to :: Rep Currency x -> Currency #

ToJSON Currency Source # 
FromJSON Currency Source # 
NFData Currency Source # 

Methods

rnf :: Currency -> () #

type Rep Currency Source # 
type Rep Currency = D1 (MetaData "Currency" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "Currency" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "curId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurrencyId)) ((:*:) (S1 (MetaSel (Just Symbol "curName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "curMinSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinScientific)))))

data ExchangeTime Source #

Constructors

ExchangeTime 

Instances

Data ExchangeTime Source # 

Methods

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

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

toConstr :: ExchangeTime -> Constr #

dataTypeOf :: ExchangeTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ExchangeTime Source # 
Generic ExchangeTime Source # 

Associated Types

type Rep ExchangeTime :: * -> * #

ToJSON ExchangeTime Source # 
FromJSON ExchangeTime Source # 
type Rep ExchangeTime Source # 
type Rep ExchangeTime = D1 (MetaData "ExchangeTime" "Coinbase.Exchange.Types.MarketData" "coinbase-exchange-0.4.0.0-KDeprrDmLO86gY1hPoWgDg" False) (C1 (MetaCons "ExchangeTime" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "timeIso") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) (S1 (MetaSel (Just Symbol "timeEpoch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))))