module Net.Weather
( Observation(..)
, APIKey
, getConditions
) where
import Control.Monad
import Control.Applicative
import Data.Text (Text)
import Data.Aeson
import Data.ByteString.Lazy.Char8 (pack)
import Network.HTTP (getResponseBody, simpleHTTP, getRequest)
import qualified Data.HashMap.Strict as H
data Observation =
Observation { obsTime :: String
, obsWeather :: String
, obsTemp :: Float
, obsRelHumidity :: String
, obsWind :: String
, obsFeelsLike :: String
} deriving (Show)
instance FromJSON Observation where
parseJSON (Object v) = Observation
<$> v .: "observation_time"
<*> v .: "weather"
<*> v .: "temp_f"
<*> v .: "relative_humidity"
<*> v .: "wind_string"
<*> v .: "feelslike_string"
parseJSON _ = mzero
type APIKey = String
getConditions :: APIKey -> String -> String -> IO (Maybe Observation)
getConditions key city state = do
obj <- evalJSONRequest $ conditionsQuery key city state
return $ obj >>= getProperty "current_observation"
getProperty :: FromJSON a => Text -> Value -> Maybe a
getProperty property (Object v) = do
val <- H.lookup property v
case fromJSON val of
Error _ -> Nothing
Success x -> Just x
getProperty _ _ = Nothing
evalJSONRequest :: FromJSON a => String -> IO (Maybe a)
evalJSONRequest request = do
body <- getResponseBody <=< simpleHTTP $ getRequest request
return . decode $ pack body
conditionsQuery :: String -> String -> String -> String
conditionsQuery key city state =
"http://api.wunderground.com/api/" ++ key
++ "/conditions/q/" ++ state
++ "/" ++ city ++ ".json"