{- | 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%\")\]\] @ -} module Finance.Quote.Yahoo (getQuote,defaultFields, QuoteField,QuoteSymbol,QuoteValue) where import qualified Network.HTTP.Simple as H (httpGet) import qualified Data.String as S (join,replace,split) import qualified Network.URI as U (parseURI,escapeURIString, isUnescapedInURI) {- License info: The license is a simple BSD3-style license available here: http://www.b7j0c.org/content/license.txt -} -- | This is the base uri to get csv quotes. baseURI = "http://finance.yahoo.com/d/quotes.csv" :: String type QuoteField = String type QuoteSymbol = String type QuoteValue = String -- | If you just want the symbol, closing price and change, use this. defaultFields = ["s","l1","c"] :: [QuoteField] -- | quoteReq will build a String representation of a Yahoo Finance CSV -- request URI. quoteReq :: [QuoteSymbol] -> [QuoteField] -> String quoteReq symbols fields = U.escapeURIString U.isUnescapedInURI (baseURI ++ "?s=" ++ (S.join "+" symbols) ++ "&f=" ++ (concat fields)) -- | 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. getQuote :: [QuoteSymbol] -> [QuoteField] -> IO (Maybe [[(QuoteField,QuoteValue)]]) getQuote symbols fields = let s = (quoteReq symbols fields) in case U.parseURI s of Nothing -> return Nothing Just uri -> do trycsv <- H.httpGet uri case trycsv of Nothing -> return Nothing Just csv -> return (Just (map (zip fields) (map (S.split ",") (lines (S.replace "\r" "" (S.replace "\"" "" csv))))))