Finance-Quote-Yahoo-0.1: Obtain quote data from finance.yahoo.comContentsIndex
Finance.Quote.Yahoo
Description

Finance.Quote.Yahoo

Finance.Quote.Yahoo is a module to obtain quote information from finance.yahoo.com, which delivers a csv file with data for various fields, which are documented at http://www.gummy-stuff.org/Yahoo-data.htm.

The only exported function is getQuote, which takes a list of quote symbols (in the finance sense of "symbol" - YHOO,GOOG etc), a list of fields, and returns a list of pairs for each symbol. Upon any problem, Nothing is returned.

Here is small complete program illustrating the use of this module

  module Main where
  import Finance.Quote.Yahoo
  quoteSymbolList = ["YHOO","^DJI"] :: [QuoteSymbol]
  quoteFieldsList = ["s","l1","c"] :: [QuoteField]
  main = do
    q <- getQuote quoteSymbolList quoteFieldsList
    case q of
      Nothing -> error "no return"
      Just l -> print l
    return ()

which outputs:

  [[("s","YHOO"),("l1","26.69"),("c","-0.28 - -1.04%")],
   [("s","^DJI"),("l1","13577.87"),("c","+76.17 - +0.56%")]]
Synopsis
getQuote :: [QuoteSymbol] -> [QuoteField] -> IO (Maybe [[(QuoteField, QuoteValue)]])
type QuoteField = String
type QuoteSymbol = String
type QuoteValue = String
Documentation
getQuote :: [QuoteSymbol] -> [QuoteField] -> IO (Maybe [[(QuoteField, QuoteValue)]])

getQuote takes two args - the symbols, and list of the fields you want. The return value is a list of lookup lists, one list per symbol requested, that match the fields you specified with their values. For example, if you were to provide

["^DJI","YHOO"] as the symbols

["s","c"] as the fields,

the response structure would be

[[("s","^DJI"),("c","13,500")], [("s","YHOO"),("c","27.00")]]

As this function is in the Maybe Monad, Nothing is returned on an error.

type QuoteField = String
type QuoteSymbol = String
type QuoteValue = String
Produced by Haddock version 0.8