yahoo-finance-api-0.1.0.0: Read quotes from Yahoo Finance API

Copyright(c) Dennis Gosnell, 2016
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Web.Yahoo.Finance.API.JSON.Internal

Description

This module contians internal types and methods for accessing the Yahoo Finance webservice APIs.

Synopsis

Documentation

newtype QueryFormat Source #

Query format query param for the Yahoo finance webservice APIs. Normally should be the string json.

Constructors

QueryFormat 

Fields

Instances

Eq QueryFormat Source # 
Data QueryFormat Source # 

Methods

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

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

toConstr :: QueryFormat -> Constr #

dataTypeOf :: QueryFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QueryFormat Source # 
Show QueryFormat Source # 
IsString QueryFormat Source # 
Generic QueryFormat Source # 

Associated Types

type Rep QueryFormat :: * -> * #

ToHttpApiData QueryFormat Source # 
type Rep QueryFormat Source # 
type Rep QueryFormat = D1 (MetaData "QueryFormat" "Web.Yahoo.Finance.API.JSON.Internal" "yahoo-finance-api-0.1.0.0-ESuJop9IQhiJIm3YctHkZl" True) (C1 (MetaCons "QueryFormat" PrefixI True) (S1 (MetaSel (Just Symbol "unQueryFormat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ViewType Source #

View type query param for the Yahoo finance webservice APIs. Normally should be the string detail.

Constructors

ViewType 

Fields

Instances

Eq ViewType Source # 
Data ViewType Source # 

Methods

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

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

toConstr :: ViewType -> Constr #

dataTypeOf :: ViewType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ViewType Source # 
Show ViewType Source # 
IsString ViewType Source # 
Generic ViewType Source # 

Associated Types

type Rep ViewType :: * -> * #

Methods

from :: ViewType -> Rep ViewType x #

to :: Rep ViewType x -> ViewType #

ToHttpApiData ViewType Source # 
type Rep ViewType Source # 
type Rep ViewType = D1 (MetaData "ViewType" "Web.Yahoo.Finance.API.JSON.Internal" "yahoo-finance-api-0.1.0.0-ESuJop9IQhiJIm3YctHkZl" True) (C1 (MetaCons "ViewType" PrefixI True) (S1 (MetaSel (Just Symbol "unViewType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype QuoteList Source #

Newtype wrapper around a list of Quotes.

Constructors

QuoteList 

Fields

type YahooFinanceJsonApi = "webservice" :> ("v1" :> ("symbols" :> (Capture "symbol_list" [StockSymbol] :> ("quote" :> (QueryParam "format" QueryFormat :> (QueryParam "view" ViewType :> Get '[JSON] QuoteList)))))) Source #

Low-level Servant definition of the Yahoo Finance webservice API.

yahooFinanceJsonBaseUrl :: BaseUrl Source #

BaseUrl for the Yahoo Finance webservice API. This represents https://finance.yahoo.com.