module Lambdabot.Plugin.Reference.Ticker (tickerPlugin) where
import Lambdabot.Plugin
import Lambdabot.Util.Browser
import Control.Applicative
import Data.List
import Network.Browser (request)
import Network.HTTP
import Text.Printf
type Ticker = ModuleT () LB
tickerPlugin :: Module ()
tickerPlugin = newModule
{ moduleCmds = return
[ (command "ticker")
{ help = say "ticker symbols. Look up quotes for symbols"
, process = tickerCmd
}
, (command "bid")
{ help = say "bid symbols. Sum up the bid and ask prices for symbols."
, process = bidsCmd
}
]
}
tickerCmd :: String -> Cmd Ticker ()
tickerCmd [] = say "Empty ticker."
tickerCmd tickers = do
quotes <- getPage $ tickerUrl $ words tickers
case [x | Just x <- map extractQuote quotes] of
[] -> say "No Result Found."
xs -> mapM_ say xs
tickerUrl :: [String] -> String
tickerUrl tickers = "http://download.finance.yahoo.com/d/quotes.csv?f=sl1cd1t1&e=.csv&s=" ++ ts
where ts = intercalate "+" $ map urlEncode tickers
extractQuote :: String -> Maybe String
extractQuote = getQuote . csv
where
getQuote [sym, price, change, date, time] =
Just $ printf "%s: %s %s@ %s %s" sym price change' date time
where change' = case words change of
("N/A":_) -> ""
[ch, _, pch] -> ch ++ " (" ++ pch ++ ") "
_ -> ""
getQuote _ = Nothing
bidsCmd :: String -> Cmd Ticker ()
bidsCmd tickers =
case words tickers of
[] -> say (printf "Invalid argument '%s'" tickers)
xs -> calcBids xs >>= say
bidsUrl :: [String] -> String
bidsUrl tickers = "http://download.finance.yahoo.com/d/quotes.csv?f=ba&e=.csv&s=" ++ ts
where ts = intercalate "+" $ map urlEncode tickers
getBidAsks :: MonadLB m => [String] -> m [Maybe (Float, Float)]
getBidAsks tickers = do
xs <- getPage $ bidsUrl tickers
return $ map (extractPrice.csv) xs
where
extractPrice :: [String] -> Maybe (Float, Float)
extractPrice [bid,ask] = liftA2 (,) (readMaybe bid) (readMaybe ask)
extractPrice _ = Nothing
type AccumVal = Either String (Float, Float)
accumOption :: AccumVal -> (String, Maybe (Float, Float)) -> AccumVal
accumOption err@(Left _) _ = err
accumOption (Right _) (ticker, Nothing) = Left $ printf "Can't find '%s'" ticker
accumOption (Right (a,b)) (('-':_), Just (a',b')) = Right (a-b', b-a')
accumOption (Right (a,b)) (_, Just (a',b')) = Right (a+a', b+b')
calcBids :: MonadLB m => [String] -> m String
calcBids ticks = do
xs <- getBidAsks $ map noPrefix ticks
return $ case foldl accumOption (Right (0,0)) (zip ticks xs) of
(Left err) -> err
(Right (bid,ask)) -> printf "%s: bid $%.02f, ask $%.02f" s bid ask
where
s = unwords ticks
noPrefix ('+':xs) = xs
noPrefix ('-':xs) = xs
noPrefix xs = xs
getPage :: MonadLB m => String -> m [String]
getPage url = do
let cleanup = (map (filter (/= '\r'))) . lines
browseLB $ do
(_, result) <- request (getRequest url)
case rspCode result of
(2,0,0) -> return (cleanup (rspBody result))
(x,y,z) -> return ["Connection error: " ++ ([x,y,z] >>= show) ++ show (rspReason result)]
csv :: String -> [String]
csv ('"':xs) = case span (/= '"') xs of
(word, '"':',':rest) -> word : csv rest
(word, '"':[]) -> word : []
_ -> error "invalid CSV"
csv xs = case span (/= ',') xs of
(word, ',':rest) -> word : csv rest
([], []) -> []
(word, []) -> [word]
_ -> error "shouldn't happen"
readMaybe :: Read a => String -> Maybe a
readMaybe x = case readsPrec 0 x of
[(y,"")] -> Just y
_ -> Nothing