{-# LANGUAGE OverloadedStrings #-}
--------------------------------------------------------------------------------
-- |
-- Module      : System.Taffybar.Widget.SimpleCommandButton
-- Copyright   : (c) Ulf Jasper
-- License     : BSD3-style (see LICENSE)
--
-- Maintainer  : Ulf Jasper <ulf.jasper@web.de>
-- Stability   : unstable
-- Portability : unportable
--
-- Simple button which runs a user defined command when being clicked
--------------------------------------------------------------------------------

module System.Taffybar.Widget.SimpleCommandButton (
  -- * Usage
  -- $usage
  simpleCommandButtonNew)
where

import           Control.Monad.IO.Class
import           GI.Gtk
import           System.Process
import qualified Data.Text as T

-- $usage
--
-- In order to use this widget add the following line to your
-- @taffybar.hs@ file:
--
-- > import System.Taffybar.Widget
-- > main = do
-- >   let cmdButton = simpleCommandButtonNew "Hello World!" "xterm -e \"echo Hello World!; read x\""
--
-- Now you can use @cmdButton@ like any other Taffybar widget.

-- | Creates a new simple command button.
simpleCommandButtonNew
  :: MonadIO m
  => T.Text -- ^ Contents of the button's label.
  -> T.Text -- ^ Command to execute. Should be in $PATH or an absolute path
  -> m Widget
simpleCommandButtonNew :: forall (m :: * -> *). MonadIO m => Text -> Text -> m Widget
simpleCommandButtonNew  Text
txt Text
cmd = do
  Button
button <- Text -> m Button
forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m Button
buttonNewWithLabel Text
txt
  SignalHandlerId
_ <- Button
-> ((?self::Button) => ButtonClickedCallback) -> m SignalHandlerId
forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> ((?self::a) => ButtonClickedCallback) -> m SignalHandlerId
onButtonClicked Button
button (((?self::Button) => ButtonClickedCallback) -> m SignalHandlerId)
-> ((?self::Button) => ButtonClickedCallback) -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ String -> IO ProcessHandle
spawnCommand (Text -> String
T.unpack Text
cmd) IO ProcessHandle -> ButtonClickedCallback -> ButtonClickedCallback
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ButtonClickedCallback
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  Button -> m Widget
forall (m :: * -> *) o. (MonadIO m, IsWidget o) => o -> m Widget
toWidget Button
button