Skip to content

Instantly share code, notes, and snippets.

@eshrh
Created August 17, 2024 05:15
Show Gist options
  • Save eshrh/f2fb6fb617714d765e6ebd0b0a05aaeb to your computer and use it in GitHub Desktop.
Save eshrh/f2fb6fb617714d765e6ebd0b0a05aaeb to your computer and use it in GitHub Desktop.
Haskell Weatherstem parser & monitor for xmobar
{-# LANGUAGE DeriveGeneric #-}
module WeatherStem (WeatherStem(..)) where
import Xmobar ( Exec(alias, rate, run) )
import Data.Aeson ( decode, FromJSON, Value(Number) )
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.ByteString.Lazy as B
import Network.HTTP.Conduit (simpleHttp)
import Data.Scientific (Scientific, toRealFloat)
import GHC.Generics (Generic)
import Data.Maybe (mapMaybe)
import qualified Data.Map as M
import Data.Map (Map)
import Text.Printf (printf)
data WeatherData = WeatherData
{ value :: Value,
sensor_name :: T.Text
}
deriving (Show, Generic)
newtype Records = Records {records :: [WeatherData]}
deriving (Show, Generic)
instance FromJSON WeatherData
instance FromJSON Records
getJSON :: IO B.ByteString
getJSON =
simpleHttp
"http://cdn.weatherstem.com/dashboard/data/dynamic/model/gatech/stadium/latest.json"
getData :: IO (Map String Double)
getData = do
j <- getJSON
return $ transformWeather (decode j :: Maybe Records)
transformWeather' :: Records -> Map String Double
transformWeather' r =
M.fromList $
mapMaybe
( \x ->
case value x of
Number n -> Just ((T.unpack . sensor_name) x, toRealFloat n)
_ -> Nothing
)
(records r)
transformWeather :: Maybe Records -> Map String Double
transformWeather = maybe M.empty transformWeather'
tempPrinter :: Double -> String
tempPrinter f = printf "%.2g°c" ((f - 32) / 1.8)
windSpeedPrinter :: Double -> String
windSpeedPrinter x = printf "%.2g m/s" (0.44704 * x)
dataLookup :: String -> (Double -> String) -> Map String Double -> String
dataLookup k f = maybe "" f . M.lookup k
weatherStemOutput :: IO String
weatherStemOutput = do
datamap <- getData
let temp = dataLookup "Thermometer" tempPrinter datamap
let hum = dataLookup "Hygrometer" show datamap
let wind = dataLookup "Anemometer" windSpeedPrinter datamap
return $ temp ++ " / " ++ hum ++ "% / " ++ wind
data WeatherStem = WeatherStem
deriving (Read, Show)
instance Exec WeatherStem where
alias WeatherStem = "ws"
run WeatherStem = weatherStemOutput
rate WeatherStem = 36000
@eshrh
Copy link
Author

eshrh commented Aug 17, 2024

Replace the url on line 32 with the json api endpoint of the weatherstem station to poll. The default url is for the bobby dodd stadium at georgia tech.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment