summaryrefslogtreecommitdiffhomepage
path: root/src/Signal.hs
blob: f634c16391295f772781d76c1e5b827394240732 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
{-# LANGUAGE DeriveDataTypeable, CPP #-}

module Signal where

import Data.Typeable (Typeable)
import Control.Concurrent
import Control.Exception hiding (handle)
import System.Posix.Signals

#ifdef DBUS
import DBus (IsVariant(..))
import Control.Monad ((>=>))

import Plugins.Utils (safeHead)
#endif

data WakeUp = WakeUp deriving (Show,Typeable)
instance Exception WakeUp

data SignalType = Wakeup
                | Reposition
                | ChangeScreen
                | Hide
                | Reveal
                | Toggle
                | TogglePersistent
    deriving (Read, Show)

#ifdef DBUS
instance IsVariant SignalType where
    toVariant   = toVariant . show
    fromVariant = fromVariant >=> parseSignalType
#endif

parseSignalType :: String -> Maybe SignalType
parseSignalType = fmap fst . safeHead . reads

-- | 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 ()