summaryrefslogtreecommitdiffhomepage
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Signal.hs33
-rw-r--r--src/Xmobar.hs25
2 files changed, 34 insertions, 24 deletions
diff --git a/src/Signal.hs b/src/Signal.hs
new file mode 100644
index 0000000..3919d86
--- /dev/null
+++ b/src/Signal.hs
@@ -0,0 +1,33 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+
+module Signal where
+
+import Data.Typeable (Typeable)
+import Control.Concurrent
+import Control.Exception hiding (handle)
+import System.Posix.Signals
+
+data WakeUp = WakeUp deriving (Show,Typeable)
+instance Exception WakeUp
+
+data SignalType = Wakeup
+ | Reposition
+ | ChangeScreen
+
+-- | Signal handling
+setupSignalHandler :: IO (MVar SignalType)
+setupSignalHandler = do
+ tid <- newEmptyMVar
+ installHandler sigUSR2 (Catch $ updatePosHandler tid) Nothing
+ installHandler sigUSR1 (Catch $ changeScreenHandler tid) Nothing
+ return tid
+
+updatePosHandler :: MVar SignalType -> IO ()
+updatePosHandler sig = do
+ putMVar sig Reposition
+ return ()
+
+changeScreenHandler :: MVar SignalType -> IO ()
+changeScreenHandler sig = do
+ putMVar sig ChangeScreen
+ return ()
diff --git a/src/Xmobar.hs b/src/Xmobar.hs
index 0b744de..6c2965c 100644
--- a/src/Xmobar.hs
+++ b/src/Xmobar.hs
@@ -39,7 +39,7 @@ import Control.Arrow ((&&&))
import Control.Monad.Reader
import Control.Concurrent
import Control.Concurrent.STM
-import Control.Exception hiding (handle)
+import Control.Exception (catch, SomeException(..))
import Data.Bits
import Config
@@ -70,11 +70,6 @@ data XConf =
runX :: XConf -> X () -> IO ()
runX xc f = runReaderT f xc
-data WakeUp = WakeUp deriving (Show,Typeable)
-instance Exception WakeUp
-
-data SignalType = Wakeup | Reposition | ChangeScreen
-
-- | Starts the main event loop and threads
startLoop :: XConf -> [[(Maybe ThreadId, TVar String)]] -> IO ()
startLoop xcfg@(XConf _ _ w _ _) vs = do
@@ -162,24 +157,6 @@ eventLoop tv xc@(XConf d _ w fs cfg) signal = do
return (ocfg {position = OnScreen 1 o})
--- | Signal handling
-setupSignalHandler :: IO (MVar SignalType)
-setupSignalHandler = do
- tid <- newEmptyMVar
- installHandler sigUSR2 (Catch $ updatePosHandler tid) Nothing
- installHandler sigUSR1 (Catch $ changeScreenHandler tid) Nothing
- return tid
-
-updatePosHandler :: MVar SignalType -> IO ()
-updatePosHandler sig = do
- putMVar sig Reposition
- return ()
-
-changeScreenHandler :: MVar SignalType -> IO ()
-changeScreenHandler sig = do
- putMVar sig ChangeScreen
- return ()
-
-- $command
-- | Runs a command as an independent thread and returns its thread id