aboutsummaryrefslogtreecommitdiff
path: root/cmd/Main.hs
blob: 6349ddee5fdf518fa98bfcc0a0a77880e9efb496 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
{-# LANGUAGE LambdaCase #-}

module Main
  ( main
  ) where

import Control.Monad (when)
import Data.Semigroup ((<>))
import Data.Version (showVersion)
import System.Exit (die)
import System.IO (IOMode(ReadMode), hGetLine, hPrint, stderr, withFile)

import Options.Applicative
  ( Parser
  , (<**>)
  , (<|>)
  , auto
  , execParser
  , flag'
  , fullDesc
  , header
  , help
  , helper
  , info
  , long
  , metavar
  , option
  , optional
  , short
  , strOption
  , switch
  )
import System.Directory (createDirectoryIfMissing)
import System.Environment.XDG.BaseDir (getUserConfigDir, getUserConfigFile)

import qualified Web.OpenWeatherMap.Client as Client

import Paths_openweathermap (version) -- from cabal
import Print (printCurrectWeather, printForecastWeather)

appName :: String
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")

data ApiKey
  = ApiKeyFile FilePath
  | ApiKey String

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")

data Weather
  = Current
  | Forecast

parseWeather :: Parser Weather
parseWeather =
  flag'
    Current
    (long "current" <> short 'n' <> help "current weather (default)") <|>
  flag' Forecast (long "forecast" <> short 'f' <> help "forecast weather") <|>
  pure Current

data Config = Config
  { apikey :: Maybe ApiKey
  , location :: Client.Location
  , weather :: Weather
  , debug :: Bool
  }

parseConfig :: Parser Config
parseConfig =
  Config <$> optional parseApiKey <*> parseLocation <*> parseWeather <*>
  switch (long "debug" <> short 'd' <> help "Enable debug")

getApiKey :: Maybe ApiKey -> IO String
getApiKey (Just (ApiKey key)) = return key
getApiKey (Just (ApiKeyFile f)) = withFile f ReadMode hGetLine
getApiKey Nothing = do
  createDirectoryIfMissing True =<< getUserConfigDir appName
  getUserConfigFile appName "key" >>= getApiKey . Just . ApiKeyFile

run :: Config -> IO ()
run cfg = do
  appid <- getApiKey . apikey $ cfg
  case weather cfg of
    Current ->
      Client.getWeather appid (location cfg) >>= \case
        Left err -> die $ show err
        Right cw -> do
          when (debug cfg) $ hPrint stderr cw
          printCurrectWeather cw
    Forecast ->
      Client.getForecast appid (location cfg) >>= \case
        Left err -> die $ show err
        Right fw -> do
          when (debug cfg) $ hPrint stderr fw
          printForecastWeather fw

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"