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.Types

Description

This module contains general types for working with all Yahoo Finance APIs.

Synopsis

Documentation

newtype StockSymbol Source #

This type is used to represent a stock symbol.

It can easily be used with the OverloadedStrings extension.

>>> :set -XOverloadedStrings
>>> "GOOG" :: StockSymbol
StockSymbol {unStockSymbol = "GOOG"}

Constructors

StockSymbol 

Fields

Instances

Eq StockSymbol Source # 
Data StockSymbol Source # 

Methods

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

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

toConstr :: StockSymbol -> Constr #

dataTypeOf :: StockSymbol -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StockSymbol Source # 
Show StockSymbol Source # 
IsString StockSymbol Source # 
Generic StockSymbol Source # 

Associated Types

type Rep StockSymbol :: * -> * #

ToHttpApiData StockSymbol Source # 
ToHttpApiData [StockSymbol] Source #

Connect separate StockSymbols with a comma.

>>> toUrlPiece (["GOOG", "YHOO", "^GSPC"] :: [StockSymbol])
"GOOG,YHOO,^GSPC"
type Rep StockSymbol Source # 
type Rep StockSymbol = D1 (MetaData "StockSymbol" "Web.Yahoo.Finance.Types" "yahoo-finance-api-0.1.0.0-ESuJop9IQhiJIm3YctHkZl" True) (C1 (MetaCons "StockSymbol" PrefixI True) (S1 (MetaSel (Just Symbol "unStockSymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))