slotThe 78d526d1dd Get rid of unused imports
Starting with 5240116f3cdf169e3aa226d9f8206a5f5b99c867 we only support
GHC versions 8.4.4 and up (more precisely, the GHC version associated
with stackage lts-12 and up).  The imports in question are now in
Prelude and need not be imported explicitly.
2020-12-14 13:41:28 +01:00

59 lines
1.8 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Util.Timer
-- Copyright : (c) Andrea Rossato and David Roundy 2007
-- License : BSD-style (see xmonad/LICENSE)
--
-- Maintainer : andrea.rossato@unibz.it
-- Stability : unstable
-- Portability : unportable
--
-- A module for setting up timers
-----------------------------------------------------------------------------
module XMonad.Util.Timer
( -- * Usage
-- $usage
startTimer
, handleTimer
, TimerId
) where
import XMonad
import Control.Concurrent
import Data.Unique
-- $usage
-- This module can be used to setup a timer to handle deferred events.
-- See 'XMonad.Layout.ShowWName' for an usage example.
type TimerId = Int
-- | Start a timer, which will send a ClientMessageEvent after some
-- time (in seconds).
startTimer :: Rational -> X TimerId
startTimer s = io $ do
u <- hashUnique <$> newUnique
xfork $ do
d <- openDisplay ""
rw <- rootWindow d $ defaultScreen d
threadDelay (fromEnum $ s * 1000000)
a <- internAtom d "XMONAD_TIMER" False
allocaXEvent $ \e -> do
setEventType e clientMessage
setClientMessageEvent e rw a 32 (fromIntegral u) currentTime
sendEvent d rw False structureNotifyMask e
sync d False
return u
-- | Given a 'TimerId' and an 'Event', run an action when the 'Event'
-- has been sent by the timer specified by the 'TimerId'
handleTimer :: TimerId -> Event -> X (Maybe a) -> X (Maybe a)
handleTimer ti (ClientMessageEvent {ev_message_type = mt, ev_data = dt}) action = do
d <- asks display
a <- io $ internAtom d "XMONAD_TIMER" False
if mt == a && dt /= [] && fromIntegral (head dt) == ti
then action
else return Nothing
handleTimer _ _ _ = return Nothing