aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorIgor Pashev <pashev.igor@gmail.com>2020-04-07 16:06:11 +0200
committerIgor Pashev <pashev.igor@gmail.com>2020-04-07 16:06:11 +0200
commit8d54b02d3c4bffbc2c5525e9fc64fac44b77ab96 (patch)
tree625ebba1e5bedc49fbccaef520f69562a86f768e
parentd808b4fd3b83cdffe8fc5bd142596b7820ee4a91 (diff)
downloadopenweathermap-8d54b02d3c4bffbc2c5525e9fc64fac44b77ab96.tar.gz
Reformat with hindent
-rw-r--r--cmd/Main.hs130
-rw-r--r--lib/Web/OpenWeatherMap/API.hs34
-rw-r--r--lib/Web/OpenWeatherMap/Client.hs45
-rw-r--r--lib/Web/OpenWeatherMap/Types/Clouds.hs8
-rw-r--r--lib/Web/OpenWeatherMap/Types/Coord.hs8
-rw-r--r--lib/Web/OpenWeatherMap/Types/CurrentWeather.hs9
-rw-r--r--lib/Web/OpenWeatherMap/Types/Main.hs9
-rw-r--r--lib/Web/OpenWeatherMap/Types/Sys.hs8
-rw-r--r--lib/Web/OpenWeatherMap/Types/Weather.hs8
-rw-r--r--lib/Web/OpenWeatherMap/Types/Wind.hs8
10 files changed, 137 insertions, 130 deletions
diff --git a/cmd/Main.hs b/cmd/Main.hs
index 645ac4b..aeb5d6f 100644
--- a/cmd/Main.hs
+++ b/cmd/Main.hs
@@ -1,8 +1,8 @@
{-# LANGUAGE LambdaCase #-}
-module Main (
- main
-) where
+module Main
+ ( main
+ ) where
import Control.Monad (when)
import Data.List (intercalate)
@@ -11,9 +11,24 @@ import Data.Version (showVersion)
import System.Exit (die)
import System.IO (IOMode(ReadMode), hGetLine, hPrint, stderr, withFile)
-import Options.Applicative (
- (<**>), (<|>), Parser, auto, execParser, fullDesc, header, help, helper,
- info, long, metavar, option, optional, short, strOption, switch
+import Options.Applicative
+ ( Parser
+ , (<**>)
+ , (<|>)
+ , auto
+ , execParser
+ , fullDesc
+ , header
+ , help
+ , helper
+ , info
+ , long
+ , metavar
+ , option
+ , optional
+ , short
+ , strOption
+ , switch
)
import System.Directory (createDirectoryIfMissing)
import System.Environment.XDG.BaseDir (getUserConfigDir, getUserConfigFile)
@@ -33,22 +48,17 @@ appName = "openweathermap"
parseLocation :: Parser Client.Location
parseLocation = byName <|> byCoord
where
- byName = Client.Name <$> strOption
- ( long "city"
- <> short 'c'
- <> metavar "CITY"
- <> help "City name" )
-
- byCoord = Client.Coord
- <$> option auto
- ( long "lat"
- <> metavar "NUM"
- <> help "Latitude in decimal degrees" )
- <*> option auto
- ( long "lon"
- <> metavar "NUM"
- <> help "Longitude in decimal degrees" )
-
+ byName =
+ Client.Name <$>
+ strOption (long "city" <> short 'c' <> metavar "CITY" <> help "City name")
+ byCoord =
+ Client.Coord <$>
+ option
+ auto
+ (long "lat" <> metavar "NUM" <> help "Latitude in decimal degrees") <*>
+ option
+ auto
+ (long "lon" <> metavar "NUM" <> help "Longitude in decimal degrees")
data ApiKey
= ApiKeyFile FilePath
@@ -57,18 +67,15 @@ data ApiKey
parseApiKey :: Parser ApiKey
parseApiKey = fromFile <|> inCmdLine
where
- fromFile = ApiKeyFile <$> strOption
- ( long "api-key-file"
- <> short 'K'
- <> metavar "APIKEYFILE"
- <> help "Read API key from this file" )
-
- inCmdLine = ApiKey <$> strOption
- ( long "api-key"
- <> short 'k'
- <> metavar "APIKEY"
- <> help "API key" )
-
+ fromFile =
+ ApiKeyFile <$>
+ strOption
+ (long "api-key-file" <> short 'K' <> metavar "APIKEYFILE" <>
+ help "Read API key from this file")
+ inCmdLine =
+ ApiKey <$>
+ strOption
+ (long "api-key" <> short 'k' <> metavar "APIKEY" <> help "API key")
data Config = Config
{ apikey :: Maybe ApiKey
@@ -77,10 +84,9 @@ data Config = Config
}
parseConfig :: Parser Config
-parseConfig = Config
- <$> optional parseApiKey
- <*> parseLocation
- <*> switch (long "debug" <> short 'd' <> help "Enable debug")
+parseConfig =
+ Config <$> optional parseApiKey <*> parseLocation <*>
+ switch (long "debug" <> short 'd' <> help "Enable debug")
getApiKey :: Maybe ApiKey -> IO String
getApiKey (Just (ApiKey key)) = return key
@@ -89,16 +95,18 @@ getApiKey Nothing = do
createDirectoryIfMissing True =<< getUserConfigDir appName
getUserConfigFile appName "key" >>= getApiKey . Just . ApiKeyFile
-
showLocation :: CurrentWeather.CurrentWeather -> String
showLocation w = city ++ maybe "" ("," ++) country ++ " " ++ coords
where
name = CurrentWeather.name w
coord = CurrentWeather.coord w
country = Sys.country . CurrentWeather.sys $ w
- city = if name /= "" then name else "<unknown>"
- coords = "("++ show (Coord.lat coord) ++ "°, "
- ++ show (Coord.lon coord) ++ "°)"
+ city =
+ if name /= ""
+ then name
+ else "<unknown>"
+ coords =
+ "(" ++ show (Coord.lat coord) ++ "°, " ++ show (Coord.lon coord) ++ "°)"
showWeather :: [Weather.Weather] -> String
showWeather w = intercalate "," $ Weather.main <$> w
@@ -125,7 +133,7 @@ showWind w = dir ++ " " ++ show speed ++ " m/s"
speed = round . Wind.speed $ w
deg = Wind.deg w
-- [ "N", "NE", "E", "SE", "S", "SW", "W", "NW" ]
- dirs = [ "↓", "↙", "←", "↖", "↑", "↗", "→", "↘" ]
+ dirs = ["↓", "↙", "←", "↖", "↑", "↗", "→", "↘"]
l = length dirs
sector = round $ (deg * fromIntegral l) / 360.0
dir = dirs !! (sector `rem` l)
@@ -138,10 +146,14 @@ showTemp m = "T " ++ temp ++ " °C"
tmin :: Int
tmax = round . k2c . Main.temp_max $ m
tmin = round . k2c . Main.temp_min $ m
- show' t = if t > 0 then "+" ++ show t else show t
- temp = if tmax /= tmin
- then show' tmin ++ ".." ++ show' tmax
- else show' tmin
+ show' t =
+ if t > 0
+ then "+" ++ show t
+ else show t
+ temp =
+ if tmax /= tmin
+ then show' tmin ++ ".." ++ show' tmax
+ else show' tmin
printWeather :: CurrentWeather.CurrentWeather -> IO ()
printWeather w = putStrLn out
@@ -150,15 +162,23 @@ printWeather w = putStrLn out
place = showLocation w
mainw = CurrentWeather.main w
wind = CurrentWeather.wind w
- out = place ++ ": " ++ intercalate ", "
- [ weather, showHumidity mainw, showPressure mainw, showTemp mainw,
- showWind wind ]
+ out =
+ place ++
+ ": " ++
+ intercalate
+ ", "
+ [ weather
+ , showHumidity mainw
+ , showPressure mainw
+ , showTemp mainw
+ , showWind wind
+ ]
run :: Config -> IO ()
run cfg = do
appid <- getApiKey . apikey $ cfg
Client.getWeather appid (location cfg) >>= \case
- Left err -> die $ show err
+ Left err -> die $ show err
Right weather -> do
when (debug cfg) $ hPrint stderr weather
printWeather weather
@@ -167,7 +187,7 @@ main :: IO ()
main = run =<< execParser opts
where
opts = info (parseConfig <**> helper) (fullDesc <> header desc)
- desc = "openweathermap "
- ++ showVersion version
- ++ " - command-line client for https://openweathermap.org/api"
-
+ desc =
+ "openweathermap " ++
+ showVersion version ++
+ " - command-line client for https://openweathermap.org/api"
diff --git a/lib/Web/OpenWeatherMap/API.hs b/lib/Web/OpenWeatherMap/API.hs
index 757a6be..8a1690e 100644
--- a/lib/Web/OpenWeatherMap/API.hs
+++ b/lib/Web/OpenWeatherMap/API.hs
@@ -2,43 +2,37 @@
Direct API functions.
For API key (a.k.a appid) refer to <http://openweathermap.org/appid>.
-}
-
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
-module Web.OpenWeatherMap.API (
- weatherByName,
- weatherByCoord
-) where
+module Web.OpenWeatherMap.API
+ ( weatherByName
+ , weatherByCoord
+ ) where
import Data.Proxy (Proxy(..))
-import Servant.API ((:>), (:<|>)(..), JSON, Get, QueryParam)
+import Servant.API ((:<|>)(..), (:>), Get, JSON, QueryParam)
import Servant.Client (ClientM, client)
import Web.OpenWeatherMap.Types.CurrentWeather (CurrentWeather)
+type GetCurrentWeather = AppId :> Get '[ JSON] CurrentWeather
-type GetCurrentWeather = AppId :> Get '[JSON] CurrentWeather
type AppId = QueryParam "appid" String
type API
- = "weather" :> QueryParam "q" String :> GetCurrentWeather
- :<|> "weather" :> QueryParam "lat" Double :> QueryParam "lon" Double
- :> GetCurrentWeather
+ = "weather" :> QueryParam "q" String :> GetCurrentWeather :<|> "weather" :> QueryParam "lat" Double :> QueryParam "lon" Double :> GetCurrentWeather
-- | Request current weather in the city.
-weatherByName
- :: Maybe String -- ^ City name, e. g. \"Moscow\" or \"Moscow,ru\".
- -> Maybe String -- ^ API key.
+weatherByName ::
+ Maybe String -- ^ City name, e. g. \"Moscow\" or \"Moscow,ru\".
+ -> Maybe String -- ^ API key.
-> ClientM CurrentWeather
-
-- | Request current weather at the geographic coordinates (in decimal degrees).
-weatherByCoord
- :: Maybe Double -- ^ Latitude, e. g. 55.7522200 for Moscow.
- -> Maybe Double -- ^ Longitude, e. g. 37.6155600 for Moscow.
- -> Maybe String -- ^ API key.
+weatherByCoord ::
+ Maybe Double -- ^ Latitude, e. g. 55.7522200 for Moscow.
+ -> Maybe Double -- ^ Longitude, e. g. 37.6155600 for Moscow.
+ -> Maybe String -- ^ API key.
-> ClientM CurrentWeather
-
weatherByName :<|> weatherByCoord = client (Proxy :: Proxy API)
-
diff --git a/lib/Web/OpenWeatherMap/Client.hs b/lib/Web/OpenWeatherMap/Client.hs
index 758ee8f..c7ad7b6 100644
--- a/lib/Web/OpenWeatherMap/Client.hs
+++ b/lib/Web/OpenWeatherMap/Client.hs
@@ -1,36 +1,42 @@
{-|
High-level client functions perfoming requests to OpenWeatherMap API.
-}
-module Web.OpenWeatherMap.Client (
- Location(..),
- getWeather
-) where
+module Web.OpenWeatherMap.Client
+ ( Location(..)
+ , getWeather
+ ) where
+
+import Network.HTTP.Client (defaultManagerSettings, newManager)
+import Servant.Client
+ ( BaseUrl(BaseUrl)
+ , ClientEnv
+ , ClientError
+ , ClientM
+ , Scheme(Http)
+ , mkClientEnv
+ , runClientM
+ )
-import Network.HTTP.Client (newManager, defaultManagerSettings)
-import Servant.Client (BaseUrl(BaseUrl), ClientEnv, mkClientEnv, ClientM, Scheme(Http), ClientError, runClientM)
-
-import Web.OpenWeatherMap.Types.CurrentWeather (CurrentWeather)
import qualified Web.OpenWeatherMap.API as API
-
+import Web.OpenWeatherMap.Types.CurrentWeather (CurrentWeather)
-- | Various way to specify location.
data Location
- = Name String -- ^ City name.
- | Coord Double Double -- ^ Geographic coordinates: latitude and longitude.
-
+ = Name String -- ^ City name.
+ | Coord Double
+ Double -- ^ Geographic coordinates: latitude and longitude.
-- | Make a request to OpenWeatherMap API
-- and return current weather in given location.
-getWeather
- :: String -- ^ API key.
+getWeather ::
+ String -- ^ API key.
-> Location
-> IO (Either ClientError CurrentWeather)
-getWeather appid loc =
- defaultEnv >>= runClientM (api loc appid)
+getWeather appid loc = defaultEnv >>= runClientM (api loc appid)
-api
- :: Location
- -> String -- ^ API key.
+api ::
+ Location
+ -> String -- ^ API key.
-> ClientM CurrentWeather
api (Name city) = API.weatherByName (Just city) . Just
api (Coord lat lon) = API.weatherByCoord (Just lat) (Just lon) . Just
@@ -44,4 +50,3 @@ defaultEnv = do
-- XXX appid is passed in clear text. Oops.
baseUrl :: BaseUrl
baseUrl = BaseUrl Http "api.openweathermap.org" 80 "/data/2.5"
-
diff --git a/lib/Web/OpenWeatherMap/Types/Clouds.hs b/lib/Web/OpenWeatherMap/Types/Clouds.hs
index 78a6e97..4aec757 100644
--- a/lib/Web/OpenWeatherMap/Types/Clouds.hs
+++ b/lib/Web/OpenWeatherMap/Types/Clouds.hs
@@ -1,16 +1,14 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-module Web.OpenWeatherMap.Types.Clouds (
- Clouds(..)
-) where
+module Web.OpenWeatherMap.Types.Clouds
+ ( Clouds(..)
+ ) where
import GHC.Generics (Generic)
import Data.Aeson (FromJSON)
-
data Clouds = Clouds
{ all :: Double
} deriving (Show, Generic, FromJSON)
-
diff --git a/lib/Web/OpenWeatherMap/Types/Coord.hs b/lib/Web/OpenWeatherMap/Types/Coord.hs
index d9a9f21..517c532 100644
--- a/lib/Web/OpenWeatherMap/Types/Coord.hs
+++ b/lib/Web/OpenWeatherMap/Types/Coord.hs
@@ -1,17 +1,15 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-module Web.OpenWeatherMap.Types.Coord (
- Coord(..)
-) where
+module Web.OpenWeatherMap.Types.Coord
+ ( Coord(..)
+ ) where
import GHC.Generics (Generic)
import Data.Aeson (FromJSON)
-
data Coord = Coord
{ lon :: Double
, lat :: Double
} deriving (Show, Generic, FromJSON)
-
diff --git a/lib/Web/OpenWeatherMap/Types/CurrentWeather.hs b/lib/Web/OpenWeatherMap/Types/CurrentWeather.hs
index 26572a7..e7d4464 100644
--- a/lib/Web/OpenWeatherMap/Types/CurrentWeather.hs
+++ b/lib/Web/OpenWeatherMap/Types/CurrentWeather.hs
@@ -1,12 +1,12 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-module Web.OpenWeatherMap.Types.CurrentWeather (
- CurrentWeather(..)
-) where
+module Web.OpenWeatherMap.Types.CurrentWeather
+ ( CurrentWeather(..)
+ ) where
-import Prelude hiding (id)
import GHC.Generics (Generic)
+import Prelude hiding (id)
import Data.Aeson (FromJSON)
@@ -32,4 +32,3 @@ data CurrentWeather = CurrentWeather
, name :: String
, cod :: Int
} deriving (Show, Generic, FromJSON)
-
diff --git a/lib/Web/OpenWeatherMap/Types/Main.hs b/lib/Web/OpenWeatherMap/Types/Main.hs
index 21b1951..8ce3f7b 100644
--- a/lib/Web/OpenWeatherMap/Types/Main.hs
+++ b/lib/Web/OpenWeatherMap/Types/Main.hs
@@ -1,16 +1,16 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-module Web.OpenWeatherMap.Types.Main (
- Main(..)
-) where
+module Web.OpenWeatherMap.Types.Main
+ ( Main(..)
+ ) where
import GHC.Generics (Generic)
import Data.Aeson (FromJSON)
-
{-# ANN module "HLint: ignore Use camelCase" #-}
+
data Main = Main
{ temp :: Double
, pressure :: Double
@@ -20,4 +20,3 @@ data Main = Main
, sea_level :: Maybe Double
, grnd_level :: Maybe Double
} deriving (Show, Generic, FromJSON)
-
diff --git a/lib/Web/OpenWeatherMap/Types/Sys.hs b/lib/Web/OpenWeatherMap/Types/Sys.hs
index 8cb932b..b416e30 100644
--- a/lib/Web/OpenWeatherMap/Types/Sys.hs
+++ b/lib/Web/OpenWeatherMap/Types/Sys.hs
@@ -1,18 +1,16 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-module Web.OpenWeatherMap.Types.Sys (
- Sys(..)
-) where
+module Web.OpenWeatherMap.Types.Sys
+ ( Sys(..)
+ ) where
import GHC.Generics (Generic)
import Data.Aeson (FromJSON)
-
data Sys = Sys
{ country :: Maybe String
, sunrise :: Int
, sunset :: Int
} deriving (Show, Generic, FromJSON)
-
diff --git a/lib/Web/OpenWeatherMap/Types/Weather.hs b/lib/Web/OpenWeatherMap/Types/Weather.hs
index 090fe0f..5df2c6e 100644
--- a/lib/Web/OpenWeatherMap/Types/Weather.hs
+++ b/lib/Web/OpenWeatherMap/Types/Weather.hs
@@ -1,19 +1,17 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-module Web.OpenWeatherMap.Types.Weather (
- Weather(..)
-) where
+module Web.OpenWeatherMap.Types.Weather
+ ( Weather(..)
+ ) where
import GHC.Generics (Generic)
import Data.Aeson (FromJSON)
-
data Weather = Weather
{ id :: Int
, main :: String
, description :: String
, icon :: String
} deriving (Show, Generic, FromJSON)
-
diff --git a/lib/Web/OpenWeatherMap/Types/Wind.hs b/lib/Web/OpenWeatherMap/Types/Wind.hs
index 8481e62..91a1b73 100644
--- a/lib/Web/OpenWeatherMap/Types/Wind.hs
+++ b/lib/Web/OpenWeatherMap/Types/Wind.hs
@@ -1,17 +1,15 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-module Web.OpenWeatherMap.Types.Wind (
- Wind(..)
-) where
+module Web.OpenWeatherMap.Types.Wind
+ ( Wind(..)
+ ) where
import GHC.Generics (Generic)
import Data.Aeson (FromJSON)
-
data Wind = Wind
{ speed :: Double
, deg :: Double
} deriving (Show, Generic, FromJSON)
-