summaryrefslogtreecommitdiffhomepage
path: root/src/Xmobar/Run
diff options
context:
space:
mode:
Diffstat (limited to 'src/Xmobar/Run')
-rw-r--r--src/Xmobar/Run/Actions.hs6
-rw-r--r--src/Xmobar/Run/Exec.hs3
-rw-r--r--src/Xmobar/Run/Loop.hs15
-rw-r--r--src/Xmobar/Run/Runnable.hs1
4 files changed, 19 insertions, 6 deletions
diff --git a/src/Xmobar/Run/Actions.hs b/src/Xmobar/Run/Actions.hs
index cbc10c5..fc9682d 100644
--- a/src/Xmobar/Run/Actions.hs
+++ b/src/Xmobar/Run/Actions.hs
@@ -12,6 +12,7 @@
module Xmobar.Run.Actions ( Button
, Action(..)
+ , isEmpty
, runAction
, runAction'
, stripActions) where
@@ -20,12 +21,17 @@ import System.Process (spawnCommand, waitForProcess)
import Control.Monad (void)
import Text.Regex (Regex, subRegex, mkRegex, matchRegex)
import Data.Word (Word32)
+import Data.Char (isSpace)
type Button = Word32
data Action = Spawn [Button] String deriving (Eq, Read, Show)
+isEmpty :: Action -> Bool
+isEmpty (Spawn _ s) = all isSpace s
+
runAction :: Action -> IO ()
+runAction a | isEmpty a = return ()
runAction (Spawn _ s) = void $ spawnCommand (s ++ " &") >>= waitForProcess
-- | Run action with stdout redirected to stderr
diff --git a/src/Xmobar/Run/Exec.hs b/src/Xmobar/Run/Exec.hs
index 1879361..e5c5c8c 100644
--- a/src/Xmobar/Run/Exec.hs
+++ b/src/Xmobar/Run/Exec.hs
@@ -21,6 +21,7 @@ module Xmobar.Run.Exec (Exec (..), tenthSeconds, doEveryTenthSeconds) where
import Prelude
import Data.Char
+import Data.Word (Word32)
import Xmobar.Run.Timer (doEveryTenthSeconds, tenthSeconds)
import Xmobar.System.Signal
@@ -37,3 +38,5 @@ class Show e => Exec e where
where go = doEveryTenthSeconds (rate e) $ run e >>= cb
trigger :: e -> (Maybe SignalType -> IO ()) -> IO ()
trigger _ sh = sh Nothing
+ onClick :: e -> Word32 -> IO ()
+ onClick _ _ = return ()
diff --git a/src/Xmobar/Run/Loop.hs b/src/Xmobar/Run/Loop.hs
index bda41ff..343a857 100644
--- a/src/Xmobar/Run/Loop.hs
+++ b/src/Xmobar/Run/Loop.hs
@@ -3,7 +3,7 @@
------------------------------------------------------------------------------
-- |
-- Module: Xmobar.Run.Loop
--- Copyright: (c) 2022 Jose Antonio Ortega Ruiz
+-- Copyright: (c) 2022, 2025 Jose Antonio Ortega Ruiz
-- License: BSD3-style (see LICENSE)
--
-- Maintainer: jao@gnu.org
@@ -28,6 +28,7 @@ import Data.Foldable (for_)
import Xmobar.System.Signal
import Xmobar.Config.Types
+import Xmobar.Config.Template (withEmptyAction)
import Xmobar.Run.Runnable (Runnable)
import Xmobar.Run.Exec (start, trigger, alias)
import Xmobar.Run.Template
@@ -53,13 +54,14 @@ refreshLockT var action = do
putTMVar var ()
return r
-type LoopFunction = TMVar SignalType -> TVar [String] -> IO ()
+type LoopFunction = [Runnable] -> TMVar SignalType -> TVar [String] -> IO ()
loop :: Config -> LoopFunction -> IO ()
loop conf looper = withDeferSignals $ do
cls <- mapM (parseTemplate (commands conf) (sepChar conf))
- (splitTemplate (alignSep conf) (template conf))
+ (splitTemplate (alignSep conf) (template conf))
let confSig = unSignalChan (signal conf)
+ runners = map (\(r, _, _) -> r) (concat cls)
sig <- maybe newEmptyTMVarIO pure confSig
unless (isJust confSig) $ setupSignalHandler sig
refLock <- newRefreshLock
@@ -68,7 +70,7 @@ loop conf looper = withDeferSignals $ do
cleanupThreads
$ \vars -> do
tv <- initLoop sig refLock vars
- looper sig tv
+ looper runners sig tv
cleanupThreads :: [[([Async ()], a)]] -> IO ()
cleanupThreads vars =
@@ -93,14 +95,15 @@ initLoop sig lock vs = do
-- | Runs a command as an independent thread and returns its Async handles
-- and the TVar the command will be writing to.
startCommand :: TMVar SignalType
- -> (Runnable,String,String)
+ -> (Runnable, String, String)
-> IO ([Async ()], TVar String)
startCommand sig (com,s,ss)
| alias com == "" = do var <- newTVarIO is
atomically $ writeTVar var (s ++ ss)
return ([], var)
| otherwise = do var <- newTVarIO is
- let cb str = atomically $ writeTVar var (s ++ str ++ ss)
+ let cb str = atomically $
+ writeTVar var (s ++ withEmptyAction str ++ ss)
a1 <- async $ start com cb
a2 <- async $ trigger com $ maybe (return ())
(atomically . putTMVar sig)
diff --git a/src/Xmobar/Run/Runnable.hs b/src/Xmobar/Run/Runnable.hs
index f89f901..a95e70b 100644
--- a/src/Xmobar/Run/Runnable.hs
+++ b/src/Xmobar/Run/Runnable.hs
@@ -32,6 +32,7 @@ instance Exec Runnable where
start (Run a) = start a
alias (Run a) = alias a
trigger (Run a) = trigger a
+ onClick (Run a) = onClick a
instance Show Runnable where
show (Run x) = "Run " ++ show x