{-# LANGUAGE OverloadedStrings #-}
--------------------------------------------------------------------------------
-- |
-- Module      : System.Taffybar.Widget.CommandRunner
-- Copyright   : (c) Arseniy Seroka
-- License     : BSD3-style (see LICENSE)
--
-- Maintainer  : Arseniy Seroka <ars.seroka@gmail.com>
-- Stability   : unstable
-- Portability : unportable
--
-- Simple function which runs user defined command and
-- returns it's output in PollingLabel widget
--------------------------------------------------------------------------------

module System.Taffybar.Widget.CommandRunner ( commandRunnerNew ) where

import           Control.Monad.IO.Class
import qualified GI.Gtk
import           System.Log.Logger
import           System.Taffybar.Util
import           System.Taffybar.Widget.Generic.PollingLabel
import           Text.Printf
import qualified Data.Text as T

-- | Creates a new command runner widget. This is a 'PollingLabel' fed by
-- regular calls to command given by argument. The results of calling this
-- function are displayed as string.
commandRunnerNew
  :: MonadIO m
  => Double -- ^ Polling period (in seconds).
  -> String -- ^ Command to execute. Should be in $PATH or an absolute path
  -> [String] -- ^ Command argument. May be @[]@
  -> T.Text -- ^ If command fails this will be displayed.
  -> m GI.Gtk.Widget
commandRunnerNew :: forall (m :: * -> *).
MonadIO m =>
Double -> String -> [String] -> Text -> m Widget
commandRunnerNew Double
interval String
cmd [String]
args Text
defaultOutput =
  Double -> IO Text -> m Widget
forall (m :: * -> *). MonadIO m => Double -> IO Text -> m Widget
pollingLabelNew Double
interval (IO Text -> m Widget) -> IO Text -> m Widget
forall a b. (a -> b) -> a -> b
$ String -> [String] -> Text -> IO Text
runCommandWithDefault String
cmd [String]
args Text
defaultOutput

runCommandWithDefault :: FilePath -> [String] -> T.Text -> IO T.Text
runCommandWithDefault :: String -> [String] -> Text -> IO Text
runCommandWithDefault String
cmd [String]
args Text
def =
  (Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n') (Text -> Text) -> IO Text -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> [String] -> IO (Either String String)
forall (m :: * -> *).
MonadIO m =>
String -> [String] -> m (Either String String)
runCommand String
cmd [String]
args IO (Either String String)
-> (Either String String -> IO Text) -> IO Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> IO Text)
-> (String -> IO Text) -> Either String String -> IO Text
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> IO Text
logError (Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> (String -> Text) -> String -> IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack))
  where logError :: String -> IO Text
logError String
err =
          String -> Priority -> String -> IO ()
logM String
"System.Taffybar.Widget.CommandRunner" Priority
ERROR
               (String -> String -> String
forall r. PrintfType r => String -> r
printf String
"Got error in CommandRunner %s" String
err) IO () -> IO Text -> IO Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
def