[Haskell-cafe] ANN: Finance.Quote.Yahoo 0.1 on hackage

Andrea Rossato mailing_list at istitutocolli.org
Sat Jul 14 10:19:22 EDT 2007


On Sat, Jul 14, 2007 at 10:20:56AM +0200, Andrea Rossato wrote:
> On Fri, Jul 13, 2007 at 09:24:48PM -0700, brad clawsie wrote:
> > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Finance-Quote-Yahoo-0.1
> > 
> > this is a simple module to get stock quote information from yahoo
> > finance, considered alpha quality
> 
> Hi,
> cool! I wanted to use it to write a small plugin for xmobar, a text
> based status bar I'm developing.[1]
> 
> But, in order to use it I would need to install:
> 2. MssingH (just for join, replace and split?) which in turns requires:

the attached patch removes the MissingH requirement, the most
important I believe.

All the best
Andrea

-------------- next part --------------
--- Finance/Quote/Yahoo.hs.orig	2007-07-14 06:18:17.000000000 +0200
+++ Finance/Quote/Yahoo.hs	2007-07-14 16:15:35.000000000 +0200
@@ -35,7 +35,6 @@
 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) 
 
@@ -63,7 +62,7 @@
 quoteReq symbols fields = 
     U.escapeURIString U.isUnescapedInURI 
          (baseURI ++ "?s=" ++ 
-          (S.join "+" symbols) ++ "&f=" ++ (concat fields))
+          (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,
@@ -92,7 +91,21 @@
           Nothing -> return Nothing
           Just csv ->
               return (Just (map (zip fields)
-                            (map (S.split ",") 
-                             (lines (S.replace "\r" "" 
-                                     (S.replace "\"" "" csv)))))) 
-                     
+                            (map (split_ ',') 
+                             (lines (remove_ '\r' 
+                                     (remove_ '\"' csv)))))) 
+
+join_ :: [a] -> [[a]] -> [a]
+join_ _ [] = []
+join_ a (s:ss) = s ++ a ++ join_ a ss
+
+remove_ :: Eq a => a -> [a] -> [a]
+remove_ c = concat . split_ c
+
+split_ :: Eq a => a -> [a] -> [[a]]
+split_ _ [] = []
+split_ c s =
+    [f] ++ split_ c (rest ss)
+        where (f,ss) = (takeWhile (/= c) s, dropWhile (/=c) s)
+              rest str | str == [] = []
+                       | otherwise = tail str


More information about the Haskell-Cafe mailing list