{- - Copyright (C) 2022 Nikola Hadžić - - This file is part of weatherhs. - - weatherhs 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 - (at your option) any later version. - - weatherhs 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 weatherhs. If not, see . -} module FormatWeather where import Data.List (intercalate) import Text.Printf (printf) import GetText import Draw {- Weather data formatting functions. -} formatWeatherTimeZone :: Word -> Bool -> String -> String -> String -> (Double, Double) -> String -> String -> String formatWeatherTimeZone termWidth pp name region country gcs tz localtime = if pp then intercalate "\n" [drawHeader termWidth H1 (printf (__ "Time zone information for %s, %s, %s") name region country), drawField termWidth (__ "Name") name, drawField termWidth (__ "Region") region, drawField termWidth (__ "Country") country, drawField termWidth (__ "Coordinates") (printf "%.2f,%.2f" (fst gcs) (snd gcs)), drawField termWidth (__ "Time zone") tz, drawField termWidth (__ "Local time") localtime, drawFooter termWidth] else printf (__ "Time zone information for %s, %s, %s:\nName: %s\nRegion: %s\nCountry: %s\nCoordinates: %.2f,%.2f\nTime zone: %s\nLocal time: %s") name region country name region country (fst gcs) (snd gcs) tz localtime data FormatWeatherAirQuality = FormatWeatherAirQuality { co :: Double, o3 :: Double, no2 :: Double, so2 :: Double, pm2_5 :: Double, pm10 :: Double, us_epa :: Word, gb_defra :: Word } deriving (Show) formatWeatherAirQuality :: Word -> Bool -> FormatWeatherAirQuality -> String formatWeatherAirQuality termWidth pp aqi = if pp then intercalate "\n" ['\n' : (drawField termWidth (__ "Carbon monoxide") (printf "%f μg/m3" (co aqi))), drawField termWidth (__ "Ozone") (printf "%f μg/m3" (o3 aqi)), drawField termWidth (__ "Nitrogen dioxide") (printf "%f μg/m3" (no2 aqi)), drawField termWidth (__ "Sulphur dioxide") (printf "%f μg/m3" (so2 aqi)), drawField termWidth (__ "PM2.5") (printf "%f μg/m3" (pm2_5 aqi)), drawField termWidth (__ "PM10") (printf "%f μg/m3" (pm10 aqi)), drawField termWidth (__ "US-EPA index") (printf "%d" (us_epa aqi)), drawField termWidth (__ "UK-DEFRA index") (printf "%d" (gb_defra aqi))] else printf (__ "\nCarbon monoxide: %f μg/m3\nOzone: %f μg/m3\nNitrogen dioxide: %f μg/m3\nSulphur dioxide: %f μg/m3\nPM2.5: %f μg/m3\nPM10: %f μg/m3\nUS-EPA index: %d\nUK-DEFRA index: %d") (co aqi) (o3 aqi) (no2 aqi) (so2 aqi) (pm2_5 aqi) (pm10 aqi) (us_epa aqi) (gb_defra aqi) formatWeatherCurrent :: Word -> Bool -> String -> String -> String -> String -> Double -> Double -> Double -> Double -> String -> Double -> Double -> Word -> String -> Double -> Double -> Double -> Double -> Word -> Word -> Double -> Double -> Double -> Maybe FormatWeatherAirQuality -> String formatWeatherCurrent termWidth pp name region country last_updated temp_c temp_f feelslike_c feelslike_f condition wind_kph wind_mph wind_degree wind_dir pressure_mb pressure_in precip_mm precip_in humidity cloud uv gust_kph gust_mph mAqi = do (if pp then intercalate "\n" [drawHeader termWidth H1 (printf (__ "Current weather information for %s, %s, %s") name region country), drawField termWidth (__ "Last updated") last_updated, drawField termWidth (__ "Condition") condition, drawField termWidth (__ "Temperature") (printf (__ "%f°C (feels like: %f°C) / %f°F (feels like: %f°F)") temp_c feelslike_c temp_f feelslike_f), drawField termWidth (__ "Wind speed") (printf "%f kph / %f mph" wind_kph wind_mph), drawField termWidth (__ "Wind direction") (printf "%u° (%s)" wind_degree wind_dir), drawField termWidth (__ "Pressure") (printf "%f mb / %f in" pressure_mb pressure_in), drawField termWidth (__ "Precipicity") (printf "%f mm / %f in" precip_mm precip_in), drawField termWidth (__ "Humidity") (printf "%u%%" humidity), drawField termWidth (__ "Clouds") (printf "%u%%" cloud), drawField termWidth (__ "UV index") (printf "%f" uv), drawField termWidth (__ "Gust speed") (printf "%f kph / %f mph" gust_kph gust_mph)] else printf (__ "Current weather information for %s, %s, %s:\nLast updated: %s\nCondition: %s\nTemperature: %f°C (feels like: %f°C) / %f°F (feels like: %f°F)\nWind speed: %f kph / %f mph\nWind direction: %u° (%s)\nPressure: %f mb / %f in\nPrecipicity: %f mm / %f in\nHumidity: %u%%\nClouds: %u%%\nUV index: %f\nGust speed: %f kph / %f mph") name region country last_updated condition temp_c feelslike_c temp_f feelslike_f wind_kph wind_mph wind_degree wind_dir pressure_mb pressure_in precip_mm precip_in humidity cloud uv gust_kph gust_mph) ++ (case mAqi of Nothing -> "" Just aqi -> (if pp then '\n' : (drawHeader termWidth H2 (__ "Air quality")) else (__ "\n\nAir quality:")) ++ formatWeatherAirQuality termWidth pp aqi) ++ if pp then '\n' : (drawFooter termWidth) else "" data FormatWeatherAlert = FormatWeatherAlert { headline :: String, msgtype :: String, severity :: String, urgency :: String, areas :: String, category :: String, certainty :: String, event :: String, note :: String, effective :: String, expires :: String, desc :: String, instruction :: String } deriving (Show) formatWeatherAlert :: Word -> Bool -> FormatWeatherAlert -> String formatWeatherAlert termWidth pp alert = if pp then intercalate "\n" ['\n' : (drawHeader termWidth H3 (printf (__ "[Severity: %s] - [Urgency: %s] | (Type: %s): %s") (severity alert) (urgency alert) (msgtype alert) (headline alert))), drawField termWidth (__ "Areas") (areas alert), drawField termWidth (__ "Category") (category alert), drawField termWidth (__ "Certainty") (certainty alert), drawField termWidth (__ "Event") (event alert), drawField termWidth (__ "Notes") (note alert), drawField termWidth (__ "Effective since") (effective alert), drawField termWidth (__ "Expires") (expires alert), drawField termWidth (__ "Description") (desc alert), drawField termWidth (__ "Instructions") (instruction alert)] else printf (__ "\n\n[Severity: %s] - [Urgency: %s] | (Type: %s): %s\nAreas: %s\nCategory: %s\nCertainty: %s\nEvent: %s\nNotes: %s\nEffective since: %s\nExpires: %s\nDescription: %s\nInstructions: %s") (severity alert) (urgency alert) (msgtype alert) (headline alert) (areas alert) (category alert) (certainty alert) (event alert) (note alert) (effective alert) (expires alert) (desc alert) (instruction alert) data FormatWeatherDay = FormatWeatherDay { maxtemp_c :: Double, maxtemp_f :: Double, mintemp_c :: Double, mintemp_f :: Double, avgtemp_c :: Double, avgtemp_f :: Double, maxwind_kph :: Double, maxwind_mph :: Double, totalprecip_mm :: Double, totalprecip_in :: Double, avgvis_km :: Double, avgvis_miles :: Double, avghumidity :: Word, condition :: String, uv :: Double, daily_chance_of_rain :: Word, daily_chance_of_snow :: Word } deriving (Show) formatWeatherDay :: Word -> Bool -> String -> FormatWeatherDay -> String formatWeatherDay termWidth pp date day = if pp then intercalate "\n" ['\n' : (drawHeader termWidth H3 date), drawField termWidth (__ "Condition") (condition day), drawField termWidth (__ "Temperature") (printf (__ "Maximum: %f°C / %f°F | Minimum: %f°C / %f°F | Average: %f°C / %f°F") (maxtemp_c day) (maxtemp_f day) (mintemp_c day) (mintemp_f day) (avgtemp_c day) (avgtemp_f day)), drawField termWidth (__ "Maximum wind speed") (printf "%f kph / %f mph" (maxwind_kph day) (maxwind_mph day)), drawField termWidth (__ "Total precipicity") (printf "%f mm / %f in" (totalprecip_mm day) (totalprecip_in day)), drawField termWidth (__ "Average visibility") (printf "%f km / %f mi" (avgvis_km day) (avgvis_miles day)), drawField termWidth (__ "Average humidity") (printf "%u%%" (avghumidity day)), drawField termWidth (__ "UV index") (printf "%f" (uv day)), drawField termWidth (__ "Chance of rain") (printf "%u%%" (daily_chance_of_rain day)), drawField termWidth (__ "Chance of snow") (printf "%u%%" (daily_chance_of_snow day))] else printf (__ "\n\n%s:\nCondition: %s\nTemperature:\n\tMaximum: %f°C / %f°F\n\tMinimum: %f°C / %f°F\n\tAverage: %f°C / %f°F\nMaximum wind speed: %f kph / %f mph\nTotal precipicity: %f mm / %f in\nAverage visibility: %f km / %f mi\nAverage humidity: %u%%\nUV index: %f\nChance of rain: %u%%\nChance of snow: %u%%") date (condition day) (maxtemp_c day) (maxtemp_f day) (mintemp_c day) (mintemp_f day) (avgtemp_c day) (avgtemp_f day) (maxwind_kph day) (maxwind_mph day) (totalprecip_mm day) (totalprecip_in day) (avgvis_km day) (avgvis_miles day) (avghumidity day) (uv day) (daily_chance_of_rain day) (daily_chance_of_snow day) data FormatWeatherAstro = FormatWeatherAstro { sunrise :: String, sunset :: String, moonrise :: String, moonset :: String, moon_phase :: String, moon_illumination :: Word } deriving (Show) formatWeatherAstro :: Word -> Bool -> FormatWeatherAstro -> String formatWeatherAstro termWidth pp astro = if pp then intercalate "\n" ['\n' : (drawField termWidth (__ "Sunrise") (sunrise astro)), drawField termWidth (__ "Sunset") (sunset astro), drawField termWidth (__ "Moonrise") (moonrise astro), drawField termWidth (__ "Moonset") (moonset astro), drawField termWidth (__ "Moon phase") (moon_phase astro), drawField termWidth (__ "Moon illumination") (printf "%u%%" (moon_illumination astro))] else printf (__ "\nSunrise: %s\nSunset: %s\nMoonrise: %s\nMoonset: %s\nMoon phase: %s\nMoon illumination: %u%%") (sunrise astro) (sunset astro) (moonrise astro) (moonset astro) (moon_phase astro) (moon_illumination astro) formatWeatherForecast :: Word -> Bool -> String -> String -> String -> Maybe [FormatWeatherAlert] -> [(String, FormatWeatherDay, FormatWeatherAstro)] -> String formatWeatherForecast termWidth pp name region country mAlerts days = do let alerts = case mAlerts of Nothing -> "" Just alerts -> (if pp then '\n' : (drawHeader termWidth H2 (__ "Alerts")) else (__ "\n\nAlerts:")) ++ (concatMap (formatWeatherAlert termWidth pp) alerts) ++ (if pp then '\n' : (drawHeader termWidth H2 (__ "Forecast")) else (__ "\n\nForecast:")) let forecast = concatMap (\day -> case day of (date, day, astro) -> (formatWeatherDay termWidth pp date day) ++ (formatWeatherAstro termWidth pp astro)) days (if pp then do drawHeader termWidth H1 (printf (__ "Weather forecast for %s, %s, %s") name region country) else printf (__ "Weather forecast for %s, %s, %s:") name region country) ++ alerts ++ forecast ++ if pp then '\n' : (drawFooter termWidth) else "" formatWeatherAstronomy :: Word -> Bool -> String -> String -> String -> FormatWeatherAstro -> String formatWeatherAstronomy termWidth pp name region country astro = (if pp then do drawHeader termWidth H1 (printf (__ "Astronomy information for %s, %s, %s") name region country) else printf (__ "Astronomy information for %s, %s, %s:") name region country) ++ (formatWeatherAstro termWidth pp astro) ++ if pp then '\n' : (drawFooter termWidth) else ""