{-# LANGUAGE OverloadedStrings #-}
module System.Taffybar.Widget.WttrIn ( textWttrNew ) where
import System.Log.Logger
import Control.Exception as E
import Control.Monad.IO.Class
import GI.Gtk
import qualified Data.Text as T
import Data.Maybe (isJust)
import Data.Text.Encoding (decodeUtf8)
import Data.ByteString.Lazy (toStrict)
import Data.ByteString (ByteString)
import Text.Regex
import Network.HTTP.Client
import Network.HTTP.Types.Status (statusIsSuccessful)
import System.Taffybar.Widget.Generic.PollingLabel
textWttrNew
:: MonadIO m
=> String
-> Double
-> m Widget
textWttrNew :: forall (m :: * -> *). MonadIO m => [Char] -> Double -> m Widget
textWttrNew [Char]
url Double
interval = Double -> IO Text -> m Widget
forall (m :: * -> *). MonadIO m => Double -> IO Text -> m Widget
pollingLabelNew Double
interval ([Char] -> IO Text
callWttr [Char]
url)
callWttr :: String -> IO T.Text
callWttr :: [Char] -> IO Text
callWttr [Char]
url = do
let unknownLocation :: Text -> Bool
unknownLocation Text
rsp =
case Text -> Text -> Maybe Text
T.stripPrefix Text
"Unknown location; please try" Text
rsp of
Maybe Text
Nothing -> Bool
False
Just Text
strippedRsp -> Text -> Int
T.length Text
strippedRsp Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Text -> Int
T.length Text
rsp
isImage :: [Char] -> Bool
isImage = Maybe [[Char]] -> Bool
forall a. Maybe a -> Bool
isJust (Maybe [[Char]] -> Bool)
-> ([Char] -> Maybe [[Char]]) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Regex -> [Char] -> Maybe [[Char]]
matchRegex (Regex -> [Char] -> Maybe [[Char]])
-> Regex -> [Char] -> Maybe [[Char]]
forall a b. (a -> b) -> a -> b
$ [Char] -> Regex
mkRegex [Char]
".png")
getResponseData :: Response ByteString -> (Bool, ByteString)
getResponseData Response ByteString
r = ( Status -> Bool
statusIsSuccessful (Status -> Bool) -> Status -> Bool
forall a b. (a -> b) -> a -> b
$ Response ByteString -> Status
forall body. Response body -> Status
responseStatus Response ByteString
r
, ByteString -> ByteString
toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Response ByteString -> ByteString
forall body. Response body -> body
responseBody Response ByteString
r)
catchAndLog :: IO (Bool, ByteString) -> IO (Bool, ByteString)
catchAndLog = (IO (Bool, ByteString)
-> (HttpException -> IO (Bool, ByteString))
-> IO (Bool, ByteString))
-> (HttpException -> IO (Bool, ByteString))
-> IO (Bool, ByteString)
-> IO (Bool, ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO (Bool, ByteString)
-> (HttpException -> IO (Bool, ByteString))
-> IO (Bool, ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch ((HttpException -> IO (Bool, ByteString))
-> IO (Bool, ByteString) -> IO (Bool, ByteString))
-> (HttpException -> IO (Bool, ByteString))
-> IO (Bool, ByteString)
-> IO (Bool, ByteString)
forall a b. (a -> b) -> a -> b
$ HttpException -> IO (Bool, ByteString)
logException
Manager
manager <- ManagerSettings -> IO Manager
newManager ManagerSettings
defaultManagerSettings
Request
request <- [Char] -> IO Request
forall (m :: * -> *). MonadThrow m => [Char] -> m Request
parseRequest [Char]
url
(Bool
isOk, ByteString
response) <- IO (Bool, ByteString) -> IO (Bool, ByteString)
catchAndLog (Response ByteString -> (Bool, ByteString)
getResponseData (Response ByteString -> (Bool, ByteString))
-> IO (Response ByteString) -> IO (Bool, ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Request -> Manager -> IO (Response ByteString)
httpLbs Request
request Manager
manager)
let body :: Text
body = ByteString -> Text
decodeUtf8 ByteString
response
if Bool -> Bool
not Bool
isOk Bool -> Bool -> Bool
|| [Char] -> Bool
isImage [Char]
url Bool -> Bool -> Bool
|| Text -> Bool
unknownLocation Text
body
then Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ Text
"✨"
else Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ Text
body
logException :: HttpException -> IO (Bool, ByteString)
logException :: HttpException -> IO (Bool, ByteString)
logException HttpException
e = do
let errmsg :: [Char]
errmsg = HttpException -> [Char]
forall a. Show a => a -> [Char]
show HttpException
e
[Char] -> Priority -> [Char] -> IO ()
logM [Char]
"System.Taffybar.Widget.WttrIn" Priority
ERROR ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$
([Char]
"Warning: Couldn't call wttr.in. \n" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
errmsg)
(Bool, ByteString) -> IO (Bool, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool, ByteString) -> IO (Bool, ByteString))
-> (Bool, ByteString) -> IO (Bool, ByteString)
forall a b. (a -> b) -> a -> b
$ (Bool
False, ByteString
"✨")