-- Author: Andy Stewart -- Maintainer: Andy Stewart -- -- Copyright (C) 2010 Andy Stewart, all rights reserved. -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . {-# LANGUAGE OverloadedStrings #-} module Google.Suggest ( suggest ) where import Data.Maybe (fromMaybe) import Network.Curl.Download import Text.XML.Light import qualified Codec.Binary.Url as Url import qualified Codec.Binary.UTF8.String as UTF8 -- | Get [(suggestions, queries)] from Google Suggest. suggest :: String -> IO (Either String [(String, Int)]) suggest keyword = do -- Build url. let url = "http://google.com/complete/search?output=toolbar" -- Request text. ++ ("&q=" ++ Url.encode (UTF8.encode keyword)) -- Request XML data. string <- openAsXML url return $ case string of Right (_:Elem element:_) -> do let qNameEqual str name = qName name == str elements = filterElementsName (qNameEqual "CompleteSuggestion") element suggestions = concatMap (filterElementsName (qNameEqual "suggestion")) elements queries = concatMap (filterElementsName (qNameEqual "num_queries")) elements if length suggestions == length queries then do let names = map (fromMaybe "" . findAttrBy (qNameEqual "data")) suggestions nums = map (\x -> case findAttrBy (qNameEqual "int") x of Just str -> read str :: Int Nothing -> 0) queries Right $ zip names nums else Left "Parse failed." _ -> Left "Parse failed."