{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module XMonad.Main (xmonad, buildLaunch, launch) where
import System.Locale.SetLocale
import qualified Control.Exception as E
import Data.Bits
import Data.List ((\\))
import Data.Foldable (traverse_)
import qualified Data.Map as M
import qualified Data.Set as S
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad (filterM, guard, unless, void, when)
import Data.Maybe (fromMaybe, isJust)
import Data.Monoid (getAll)
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
import Graphics.X11.Xlib.Extras
import XMonad.Core
import qualified XMonad.Config as Default
import XMonad.StackSet (new, floating, member)
import qualified XMonad.StackSet as W
import XMonad.Operations
import System.IO
import System.Directory
import System.Info
import System.Environment (getArgs, getProgName, withArgs)
import System.Posix.Process (executeFile)
import System.Exit (exitFailure)
import System.FilePath
import Paths_xmonad (version)
import Data.Version (showVersion)
import Graphics.X11.Xinerama (compiledWithXinerama)
import Graphics.X11.Xrandr (xrrQueryExtension, xrrUpdateConfiguration)
xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
xmonad :: forall (l :: * -> *).
(LayoutClass l KeySym, Read (l KeySym)) =>
XConfig l -> IO ()
xmonad XConfig l
conf = do
IO ()
forall (m :: * -> *). MonadIO m => m ()
installSignalHandlers
Directories
dirs <- IO Directories
getDirectories
let launch' :: [String] -> IO ()
launch' [String]
args = do
IO () -> IO ()
forall (m :: * -> *). MonadIO m => IO () -> m ()
catchIO (Directories -> IO ()
buildLaunch Directories
dirs)
conf' :: XConfig Layout
conf'@XConfig { layoutHook :: forall (l :: * -> *). XConfig l -> l KeySym
layoutHook = Layout l KeySym
l }
<- XConfig l -> [String] -> XConfig Layout -> IO (XConfig Layout)
forall (l :: * -> *).
XConfig l -> [String] -> XConfig Layout -> IO (XConfig Layout)
handleExtraArgs XConfig l
conf [String]
args XConfig l
conf{ layoutHook = Layout (layoutHook conf) }
[String] -> IO () -> IO ()
forall a. [String] -> IO a -> IO a
withArgs [] (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ XConfig l -> Directories -> IO ()
forall (l :: * -> *).
(LayoutClass l KeySym, Read (l KeySym)) =>
XConfig l -> Directories -> IO ()
launch (XConfig Layout
conf' { layoutHook = l }) Directories
dirs
[String]
args <- IO [String]
getArgs
case [String]
args of
[String
"--help"] -> IO ()
usage
[String
"--recompile"] -> Directories -> Bool -> IO Bool
forall (m :: * -> *). MonadIO m => Directories -> Bool -> m Bool
recompile Directories
dirs Bool
True IO Bool -> (Bool -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Bool -> IO () -> IO ()) -> IO () -> Bool -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless IO ()
forall a. IO a
exitFailure
[String
"--restart"] -> IO ()
sendRestart
[String
"--version"] -> String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords [String]
shortVersion
[String
"--verbose-version"] -> String -> IO ()
putStrLn (String -> IO ()) -> ([String] -> String) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unwords ([String] -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$ [String]
shortVersion [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
longVersion
String
"--replace" : [String]
args' -> IO ()
sendReplace IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [String] -> IO ()
launch' [String]
args'
[String]
_ -> [String] -> IO ()
launch' [String]
args
where
shortVersion :: [String]
shortVersion = [String
"xmonad", Version -> String
showVersion Version
version]
longVersion :: [String]
longVersion = [ String
"compiled by", String
compilerName, Version -> String
showVersion Version
compilerVersion
, String
"for", String
arch String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
os
, String
"\nXinerama:", Bool -> String
forall a. Show a => a -> String
show Bool
compiledWithXinerama ]
usage :: IO ()
usage :: IO ()
usage = do
String
self <- IO String
getProgName
String -> IO ()
putStr (String -> IO ()) -> ([String] -> String) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines ([String] -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$
[ String
"Usage: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
self String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" [OPTION]"
, String
"Options:"
, String
" --help Print this message"
, String
" --version Print the version number"
, String
" --recompile Recompile your xmonad.hs"
, String
" --replace Replace the running window manager with xmonad"
, String
" --restart Request a running xmonad process to restart"
]
buildLaunch :: Directories -> IO ()
buildLaunch :: Directories -> IO ()
buildLaunch Directories
dirs = do
String
whoami <- IO String
getProgName
let bin :: String
bin = Directories -> String
binFileName Directories
dirs
let compiledConfig :: String
compiledConfig = String -> String
takeFileName String
bin
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (String
whoami String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
compiledConfig) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"XMonad is recompiling and replacing itself with another XMonad process because the current process is called "
, String -> String
forall a. Show a => a -> String
show String
whoami
, String
" but the compiled configuration should be called "
, String -> String
forall a. Show a => a -> String
show String
compiledConfig
]
Directories -> Bool -> IO Bool
forall (m :: * -> *). MonadIO m => Directories -> Bool -> m Bool
recompile Directories
dirs Bool
False
[String]
args <- IO [String]
getArgs
String -> Bool -> [String] -> Maybe [(String, String)] -> IO ()
forall a.
String -> Bool -> [String] -> Maybe [(String, String)] -> IO a
executeFile String
bin Bool
False [String]
args Maybe [(String, String)]
forall a. Maybe a
Nothing
launch :: (LayoutClass l Window, Read (l Window)) => XConfig l -> Directories -> IO ()
launch :: forall (l :: * -> *).
(LayoutClass l KeySym, Read (l KeySym)) =>
XConfig l -> Directories -> IO ()
launch XConfig l
initxmc Directories
drs = do
Category -> Maybe String -> IO (Maybe String)
setLocale Category
LC_ALL (String -> Maybe String
forall a. a -> Maybe a
Just String
"")
IO ()
forall (m :: * -> *). MonadIO m => m ()
installSignalHandlers
let xmc :: XConfig Layout
xmc = XConfig l
initxmc { layoutHook = Layout $ layoutHook initxmc }
Display
dpy <- String -> IO Display
openDisplay String
""
let dflt :: EventType
dflt = Display -> EventType
defaultScreen Display
dpy
KeySym
rootw <- Display -> EventType -> IO KeySym
rootWindow Display
dpy EventType
dflt
Display -> KeySym -> KeySym -> IO ()
selectInput Display
dpy KeySym
rootw (KeySym -> IO ()) -> KeySym -> IO ()
forall a b. (a -> b) -> a -> b
$ XConfig l -> KeySym
forall (l :: * -> *). XConfig l -> KeySym
rootMask XConfig l
initxmc
Display -> Bool -> IO ()
sync Display
dpy Bool
False
IO ()
xSetErrorHandler
[Rectangle]
xinesc <- Display -> IO [Rectangle]
forall (m :: * -> *). MonadIO m => Display -> m [Rectangle]
getCleanedScreenInfo Display
dpy
KeySym
nbc <- do Maybe KeySym
v <- Display -> String -> IO (Maybe KeySym)
initColor Display
dpy (String -> IO (Maybe KeySym)) -> String -> IO (Maybe KeySym)
forall a b. (a -> b) -> a -> b
$ XConfig Layout -> String
forall (l :: * -> *). XConfig l -> String
normalBorderColor XConfig Layout
xmc
Just KeySym
nbc_ <- Display -> String -> IO (Maybe KeySym)
initColor Display
dpy (String -> IO (Maybe KeySym)) -> String -> IO (Maybe KeySym)
forall a b. (a -> b) -> a -> b
$ XConfig (Choose Tall (Choose (Mirror Tall) Full)) -> String
forall (l :: * -> *). XConfig l -> String
normalBorderColor XConfig (Choose Tall (Choose (Mirror Tall) Full))
forall a. Default a => a
Default.def
KeySym -> IO KeySym
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (KeySym -> Maybe KeySym -> KeySym
forall a. a -> Maybe a -> a
fromMaybe KeySym
nbc_ Maybe KeySym
v)
KeySym
fbc <- do Maybe KeySym
v <- Display -> String -> IO (Maybe KeySym)
initColor Display
dpy (String -> IO (Maybe KeySym)) -> String -> IO (Maybe KeySym)
forall a b. (a -> b) -> a -> b
$ XConfig Layout -> String
forall (l :: * -> *). XConfig l -> String
focusedBorderColor XConfig Layout
xmc
Just KeySym
fbc_ <- Display -> String -> IO (Maybe KeySym)
initColor Display
dpy (String -> IO (Maybe KeySym)) -> String -> IO (Maybe KeySym)
forall a b. (a -> b) -> a -> b
$ XConfig (Choose Tall (Choose (Mirror Tall) Full)) -> String
forall (l :: * -> *). XConfig l -> String
focusedBorderColor XConfig (Choose Tall (Choose (Mirror Tall) Full))
forall a. Default a => a
Default.def
KeySym -> IO KeySym
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (KeySym -> Maybe KeySym -> KeySym
forall a. a -> Maybe a -> a
fromMaybe KeySym
fbc_ Maybe KeySym
v)
Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdout BufferMode
NoBuffering
let layout :: Layout KeySym
layout = XConfig Layout -> Layout KeySym
forall (l :: * -> *). XConfig l -> l KeySym
layoutHook XConfig Layout
xmc
initialWinset :: StackSet String (Layout KeySym) a ScreenId ScreenDetail
initialWinset = let padToLen :: Int -> [String] -> [String]
padToLen Int
n [String]
xs = Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
n ([String] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
xs)) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
xs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
forall a. a -> [a]
repeat String
""
in Layout KeySym
-> [String]
-> [ScreenDetail]
-> StackSet String (Layout KeySym) a ScreenId ScreenDetail
forall s l i sd a.
Integral s =>
l -> [i] -> [sd] -> StackSet i l a s sd
new Layout KeySym
layout (Int -> [String] -> [String]
padToLen ([Rectangle] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Rectangle]
xinesc) (XConfig Layout -> [String]
forall (l :: * -> *). XConfig l -> [String]
workspaces XConfig Layout
xmc)) ([ScreenDetail]
-> StackSet String (Layout KeySym) a ScreenId ScreenDetail)
-> [ScreenDetail]
-> StackSet String (Layout KeySym) a ScreenId ScreenDetail
forall a b. (a -> b) -> a -> b
$ (Rectangle -> ScreenDetail) -> [Rectangle] -> [ScreenDetail]
forall a b. (a -> b) -> [a] -> [b]
map Rectangle -> ScreenDetail
SD [Rectangle]
xinesc
cf :: XConf
cf = XConf
{ display :: Display
display = Display
dpy
, config :: XConfig Layout
config = XConfig Layout
xmc
, theRoot :: KeySym
theRoot = KeySym
rootw
, normalBorder :: KeySym
normalBorder = KeySym
nbc
, focusedBorder :: KeySym
focusedBorder = KeySym
fbc
, keyActions :: Map (ButtonMask, KeySym) (X ())
keyActions = XConfig Layout -> XConfig Layout -> Map (ButtonMask, KeySym) (X ())
forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (ButtonMask, KeySym) (X ())
keys XConfig Layout
xmc XConfig Layout
xmc
, buttonActions :: Map (ButtonMask, EventType) (KeySym -> X ())
buttonActions = XConfig Layout
-> XConfig Layout -> Map (ButtonMask, EventType) (KeySym -> X ())
forall (l :: * -> *).
XConfig l
-> XConfig Layout -> Map (ButtonMask, EventType) (KeySym -> X ())
mouseBindings XConfig Layout
xmc XConfig Layout
xmc
, mouseFocused :: Bool
mouseFocused = Bool
False
, mousePosition :: Maybe (Position, Position)
mousePosition = Maybe (Position, Position)
forall a. Maybe a
Nothing
, currentEvent :: Maybe Event
currentEvent = Maybe Event
forall a. Maybe a
Nothing
, directories :: Directories
directories = Directories
drs
}
st :: XState
st = XState
{ windowset :: WindowSet
windowset = WindowSet
forall {a}. StackSet String (Layout KeySym) a ScreenId ScreenDetail
initialWinset
, numberlockMask :: ButtonMask
numberlockMask = ButtonMask
0
, mapped :: Set KeySym
mapped = Set KeySym
forall a. Set a
S.empty
, waitingUnmap :: Map KeySym Int
waitingUnmap = Map KeySym Int
forall k a. Map k a
M.empty
, dragging :: Maybe (Position -> Position -> X (), X ())
dragging = Maybe (Position -> Position -> X (), X ())
forall a. Maybe a
Nothing
, extensibleState :: Map String (Either String StateExtension)
extensibleState = Map String (Either String StateExtension)
forall k a. Map k a
M.empty
}
(XEventPtr -> IO (Any, XState)) -> IO (Any, XState)
forall a. (XEventPtr -> IO a) -> IO a
allocaXEvent ((XEventPtr -> IO (Any, XState)) -> IO (Any, XState))
-> (XEventPtr -> IO (Any, XState)) -> IO (Any, XState)
forall a b. (a -> b) -> a -> b
$ \XEventPtr
e ->
XConf -> XState -> X Any -> IO (Any, XState)
forall a. XConf -> XState -> X a -> IO (a, XState)
runX XConf
cf XState
st (X Any -> IO (Any, XState)) -> X Any -> IO (Any, XState)
forall a b. (a -> b) -> a -> b
$ do
Maybe XState
serializedSt <- do
String
path <- (XConf -> String) -> X String
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ((XConf -> String) -> X String) -> (XConf -> String) -> X String
forall a b. (a -> b) -> a -> b
$ Directories -> String
stateFileName (Directories -> String)
-> (XConf -> Directories) -> XConf -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Directories
directories
Bool
exists <- IO Bool -> X Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (String -> IO Bool
doesFileExist String
path)
if Bool
exists then XConfig l -> X (Maybe XState)
forall (l :: * -> *).
(LayoutClass l KeySym, Read (l KeySym)) =>
XConfig l -> X (Maybe XState)
readStateFile XConfig l
initxmc else Maybe XState -> X (Maybe XState)
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe XState
forall a. Maybe a
Nothing
let extst :: Map String (Either String StateExtension)
extst = Map String (Either String StateExtension)
-> (XState -> Map String (Either String StateExtension))
-> Maybe XState
-> Map String (Either String StateExtension)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Map String (Either String StateExtension)
forall k a. Map k a
M.empty XState -> Map String (Either String StateExtension)
extensibleState Maybe XState
serializedSt
(XState -> XState) -> X ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\XState
s -> XState
s {extensibleState = extst})
X ()
cacheNumlockMask
X ()
grabKeys
X ()
grabButtons
IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display -> Bool -> IO ()
sync Display
dpy Bool
False
[KeySym]
ws <- IO [KeySym] -> X [KeySym]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO [KeySym] -> X [KeySym]) -> IO [KeySym] -> X [KeySym]
forall a b. (a -> b) -> a -> b
$ Display -> KeySym -> IO [KeySym]
scan Display
dpy KeySym
rootw
let winset :: WindowSet
winset = WindowSet -> (XState -> WindowSet) -> Maybe XState -> WindowSet
forall b a. b -> (a -> b) -> Maybe a -> b
maybe WindowSet
forall {a}. StackSet String (Layout KeySym) a ScreenId ScreenDetail
initialWinset XState -> WindowSet
windowset Maybe XState
serializedSt
(WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> ([KeySym] -> WindowSet -> WindowSet) -> [KeySym] -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSet -> WindowSet -> WindowSet
forall a b. a -> b -> a
const (WindowSet -> WindowSet -> WindowSet)
-> ([KeySym] -> WindowSet) -> [KeySym] -> WindowSet -> WindowSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (KeySym -> WindowSet -> WindowSet)
-> WindowSet -> [KeySym] -> WindowSet
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr KeySym -> WindowSet -> WindowSet
forall a i l s sd.
Ord a =>
a -> StackSet i l a s sd -> StackSet i l a s sd
W.delete WindowSet
winset ([KeySym] -> X ()) -> [KeySym] -> X ()
forall a b. (a -> b) -> a -> b
$ WindowSet -> [KeySym]
forall a i l s sd. Eq a => StackSet i l a s sd -> [a]
W.allWindows WindowSet
winset [KeySym] -> [KeySym] -> [KeySym]
forall a. Eq a => [a] -> [a] -> [a]
\\ [KeySym]
ws
(KeySym -> X ()) -> [KeySym] -> X ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ KeySym -> X ()
manage ([KeySym]
ws [KeySym] -> [KeySym] -> [KeySym]
forall a. Eq a => [a] -> [a] -> [a]
\\ WindowSet -> [KeySym]
forall a i l s sd. Eq a => StackSet i l a s sd -> [a]
W.allWindows WindowSet
winset)
X () -> X (Maybe ())
forall a. X a -> X (Maybe a)
userCode (X () -> X (Maybe ())) -> X () -> X (Maybe ())
forall a b. (a -> b) -> a -> b
$ XConfig l -> X ()
forall (l :: * -> *). XConfig l -> X ()
startupHook XConfig l
initxmc
Maybe (CInt, CInt)
rrData <- IO (Maybe (CInt, CInt)) -> X (Maybe (CInt, CInt))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO (Maybe (CInt, CInt)) -> X (Maybe (CInt, CInt)))
-> IO (Maybe (CInt, CInt)) -> X (Maybe (CInt, CInt))
forall a b. (a -> b) -> a -> b
$ Display -> IO (Maybe (CInt, CInt))
xrrQueryExtension Display
dpy
Display -> XEventPtr -> Maybe (CInt, CInt) -> X Any
forall {a} {b}. Display -> XEventPtr -> Maybe a -> X b
mainLoop Display
dpy XEventPtr
e Maybe (CInt, CInt)
rrData
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
prehandle :: Event -> X ()
prehandle Event
e = let mouse :: Maybe (Position, Position)
mouse = do Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Event -> EventType
ev_event_type Event
e EventType -> [EventType] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [EventType]
evs)
(Position, Position) -> Maybe (Position, Position)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Event -> CInt
ev_x_root Event
e)
,CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Event -> CInt
ev_y_root Event
e))
in (XConf -> XConf) -> X () -> X ()
forall a. (XConf -> XConf) -> X a -> X a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\XConf
c -> XConf
c { mousePosition = mouse, currentEvent = Just e }) (Event -> X ()
handleWithHook Event
e)
evs :: [EventType]
evs = [ EventType
keyPress, EventType
keyRelease, EventType
enterNotify, EventType
leaveNotify
, EventType
buttonPress, EventType
buttonRelease]
rrUpdate :: XEventPtr -> Maybe a -> IO ()
rrUpdate XEventPtr
e Maybe a
r = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe a -> Bool
forall a. Maybe a -> Bool
isJust Maybe a
r) (IO CInt -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (XEventPtr -> IO CInt
xrrUpdateConfiguration XEventPtr
e))
mainLoop :: Display -> XEventPtr -> Maybe a -> X b
mainLoop Display
d XEventPtr
e Maybe a
r = IO Event -> X Event
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (Display -> XEventPtr -> IO ()
nextEvent Display
d XEventPtr
e IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> XEventPtr -> Maybe a -> IO ()
forall {a}. XEventPtr -> Maybe a -> IO ()
rrUpdate XEventPtr
e Maybe a
r IO () -> IO Event -> IO Event
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> XEventPtr -> IO Event
getEvent XEventPtr
e) X Event -> (Event -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Event -> X ()
prehandle X () -> X b -> X b
forall a b. X a -> X b -> X b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Display -> XEventPtr -> Maybe a -> X b
mainLoop Display
d XEventPtr
e Maybe a
r
handleWithHook :: Event -> X ()
handleWithHook :: Event -> X ()
handleWithHook Event
e = do
Event -> X All
evHook <- (XConf -> Event -> X All) -> X (Event -> X All)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> Event -> X All
forall (l :: * -> *). XConfig l -> Event -> X All
handleEventHook (XConfig Layout -> Event -> X All)
-> (XConf -> XConfig Layout) -> XConf -> Event -> X All
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config)
X Bool -> X () -> X ()
whenX (Bool -> X Bool -> X Bool
forall a. a -> X a -> X a
userCodeDef Bool
True (X Bool -> X Bool) -> X Bool -> X Bool
forall a b. (a -> b) -> a -> b
$ All -> Bool
getAll (All -> Bool) -> X All -> X Bool
forall a b. (a -> b) -> X a -> X b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Event -> X All
evHook Event
e) (Event -> X ()
handle Event
e)
handle :: Event -> X ()
handle :: Event -> X ()
handle (KeyEvent {ev_event_type :: Event -> EventType
ev_event_type = EventType
t, ev_state :: Event -> ButtonMask
ev_state = ButtonMask
m, ev_keycode :: Event -> KeyCode
ev_keycode = KeyCode
code})
| EventType
t EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
keyPress = (Display -> X ()) -> X ()
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X ()) -> X ()) -> (Display -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Display
dpy -> do
KeySym
s <- IO KeySym -> X KeySym
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO KeySym -> X KeySym) -> IO KeySym -> X KeySym
forall a b. (a -> b) -> a -> b
$ Display -> KeyCode -> CInt -> IO KeySym
keycodeToKeysym Display
dpy KeyCode
code CInt
0
ButtonMask
mClean <- ButtonMask -> X ButtonMask
cleanMask ButtonMask
m
Map (ButtonMask, KeySym) (X ())
ks <- (XConf -> Map (ButtonMask, KeySym) (X ()))
-> X (Map (ButtonMask, KeySym) (X ()))
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Map (ButtonMask, KeySym) (X ())
keyActions
() -> X () -> X ()
forall a. a -> X a -> X a
userCodeDef () (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ Maybe (X ()) -> (X () -> X ()) -> X ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust ((ButtonMask, KeySym)
-> Map (ButtonMask, KeySym) (X ()) -> Maybe (X ())
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ButtonMask
mClean, KeySym
s) Map (ButtonMask, KeySym) (X ())
ks) X () -> X ()
forall a. a -> a
id
handle (MapRequestEvent {ev_window :: Event -> KeySym
ev_window = KeySym
w}) = (Display -> X ()) -> X ()
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X ()) -> X ()) -> (Display -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Display
dpy -> do
Display -> KeySym -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes Display
dpy KeySym
w ((WindowAttributes -> X ()) -> X ())
-> (WindowAttributes -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \WindowAttributes
wa -> do
Bool
managed <- KeySym -> X Bool
isClient KeySym
w
Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (WindowAttributes -> Bool
wa_override_redirect WindowAttributes
wa) Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
managed) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ KeySym -> X ()
manage KeySym
w
handle e :: Event
e@(DestroyWindowEvent {ev_window :: Event -> KeySym
ev_window = KeySym
w}) = do
X Bool -> X () -> X ()
whenX (KeySym -> X Bool
isClient KeySym
w) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ do
KeySym -> X ()
unmanage KeySym
w
(XState -> XState) -> X ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\XState
s -> XState
s { mapped = S.delete w (mapped s)
, waitingUnmap = M.delete w (waitingUnmap s)})
Event -> X ()
forall a. Message a => a -> X ()
broadcastMessage Event
e
handle (UnmapEvent {ev_window :: Event -> KeySym
ev_window = KeySym
w, ev_send_event :: Event -> Bool
ev_send_event = Bool
synthetic}) = X Bool -> X () -> X ()
whenX (KeySym -> X Bool
isClient KeySym
w) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ do
Int
e <- (XState -> Int) -> X Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (Maybe Int -> Int) -> (XState -> Maybe Int) -> XState -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeySym -> Map KeySym Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup KeySym
w (Map KeySym Int -> Maybe Int)
-> (XState -> Map KeySym Int) -> XState -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XState -> Map KeySym Int
waitingUnmap)
if Bool
synthetic Bool -> Bool -> Bool
|| Int
e Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then KeySym -> X ()
unmanage KeySym
w
else (XState -> XState) -> X ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\XState
s -> XState
s { waitingUnmap = M.update mpred w (waitingUnmap s) })
where mpred :: a -> Maybe a
mpred a
1 = Maybe a
forall a. Maybe a
Nothing
mpred a
n = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Enum a => a -> a
pred a
n
handle e :: Event
e@(MappingNotifyEvent {}) = do
IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Event -> IO ()
refreshKeyboardMapping Event
e
Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Event -> CInt
ev_request Event
e CInt -> [CInt] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [CInt
mappingKeyboard, CInt
mappingModifier]) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ do
X ()
cacheNumlockMask
X ()
grabKeys
handle e :: Event
e@(ButtonEvent {ev_event_type :: Event -> EventType
ev_event_type = EventType
t})
| EventType
t EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
buttonRelease = do
Maybe (Position -> Position -> X (), X ())
drag <- (XState -> Maybe (Position -> Position -> X (), X ()))
-> X (Maybe (Position -> Position -> X (), X ()))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> Maybe (Position -> Position -> X (), X ())
dragging
case Maybe (Position -> Position -> X (), X ())
drag of
Just (Position -> Position -> X ()
_,X ()
f) -> (XState -> XState) -> X ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\XState
s -> XState
s { dragging = Nothing }) X () -> X () -> X ()
forall a b. X a -> X b -> X b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> X ()
f
Maybe (Position -> Position -> X (), X ())
Nothing -> Event -> X ()
forall a. Message a => a -> X ()
broadcastMessage Event
e
handle e :: Event
e@(MotionEvent {ev_event_type :: Event -> EventType
ev_event_type = EventType
_t, ev_x :: Event -> CInt
ev_x = CInt
x, ev_y :: Event -> CInt
ev_y = CInt
y}) = do
Maybe (Position -> Position -> X (), X ())
drag <- (XState -> Maybe (Position -> Position -> X (), X ()))
-> X (Maybe (Position -> Position -> X (), X ()))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> Maybe (Position -> Position -> X (), X ())
dragging
case Maybe (Position -> Position -> X (), X ())
drag of
Just (Position -> Position -> X ()
d,X ()
_) -> Position -> Position -> X ()
d (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x) (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
y)
Maybe (Position -> Position -> X (), X ())
Nothing -> Event -> X ()
forall a. Message a => a -> X ()
broadcastMessage Event
e
handle e :: Event
e@(ButtonEvent {ev_window :: Event -> KeySym
ev_window = KeySym
w,ev_event_type :: Event -> EventType
ev_event_type = EventType
t,ev_button :: Event -> EventType
ev_button = EventType
b })
| EventType
t EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
buttonPress = do
Display
dpy <- (XConf -> Display) -> X Display
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Display
display
Bool
isr <- KeySym -> X Bool
isRoot KeySym
w
ButtonMask
m <- ButtonMask -> X ButtonMask
cleanMask (ButtonMask -> X ButtonMask) -> ButtonMask -> X ButtonMask
forall a b. (a -> b) -> a -> b
$ Event -> ButtonMask
ev_state Event
e
Maybe (KeySym -> X ())
mact <- (XConf -> Maybe (KeySym -> X ())) -> X (Maybe (KeySym -> X ()))
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ((ButtonMask, EventType)
-> Map (ButtonMask, EventType) (KeySym -> X ())
-> Maybe (KeySym -> X ())
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ButtonMask
m, EventType
b) (Map (ButtonMask, EventType) (KeySym -> X ())
-> Maybe (KeySym -> X ()))
-> (XConf -> Map (ButtonMask, EventType) (KeySym -> X ()))
-> XConf
-> Maybe (KeySym -> X ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Map (ButtonMask, EventType) (KeySym -> X ())
buttonActions)
case Maybe (KeySym -> X ())
mact of
Just KeySym -> X ()
act | Bool
isr -> KeySym -> X ()
act (KeySym -> X ()) -> KeySym -> X ()
forall a b. (a -> b) -> a -> b
$ Event -> KeySym
ev_subwindow Event
e
Maybe (KeySym -> X ())
_ -> do
KeySym -> X ()
focus KeySym
w
Bool
ctf <- (XConf -> Bool) -> X Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> Bool
forall (l :: * -> *). XConfig l -> Bool
clickJustFocuses (XConfig Layout -> Bool)
-> (XConf -> XConfig Layout) -> XConf -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config)
Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
ctf (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (Display -> CInt -> KeySym -> IO ()
allowEvents Display
dpy CInt
replayPointer KeySym
currentTime)
Event -> X ()
forall a. Message a => a -> X ()
broadcastMessage Event
e
handle e :: Event
e@(CrossingEvent {ev_window :: Event -> KeySym
ev_window = KeySym
w, ev_event_type :: Event -> EventType
ev_event_type = EventType
t})
| EventType
t EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
enterNotify Bool -> Bool -> Bool
&& Event -> CInt
ev_mode Event
e CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
notifyNormal
= X Bool -> X () -> X ()
whenX ((XConf -> Bool) -> X Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ((XConf -> Bool) -> X Bool) -> (XConf -> Bool) -> X Bool
forall a b. (a -> b) -> a -> b
$ XConfig Layout -> Bool
forall (l :: * -> *). XConfig l -> Bool
focusFollowsMouse (XConfig Layout -> Bool)
-> (XConf -> XConfig Layout) -> XConf -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ do
Display
dpy <- (XConf -> Display) -> X Display
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Display
display
KeySym
root <- (XConf -> KeySym) -> X KeySym
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> KeySym
theRoot
(Bool
_, KeySym
_, KeySym
w', CInt
_, CInt
_, CInt
_, CInt
_, ButtonMask
_) <- IO (Bool, KeySym, KeySym, CInt, CInt, CInt, CInt, ButtonMask)
-> X (Bool, KeySym, KeySym, CInt, CInt, CInt, CInt, ButtonMask)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO (Bool, KeySym, KeySym, CInt, CInt, CInt, CInt, ButtonMask)
-> X (Bool, KeySym, KeySym, CInt, CInt, CInt, CInt, ButtonMask))
-> IO (Bool, KeySym, KeySym, CInt, CInt, CInt, CInt, ButtonMask)
-> X (Bool, KeySym, KeySym, CInt, CInt, CInt, CInt, ButtonMask)
forall a b. (a -> b) -> a -> b
$ Display
-> KeySym
-> IO (Bool, KeySym, KeySym, CInt, CInt, CInt, CInt, ButtonMask)
queryPointer Display
dpy KeySym
root
Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (KeySym
w' KeySym -> KeySym -> Bool
forall a. Eq a => a -> a -> Bool
== KeySym
0 Bool -> Bool -> Bool
|| KeySym
w KeySym -> KeySym -> Bool
forall a. Eq a => a -> a -> Bool
== KeySym
w') (KeySym -> X ()
focus KeySym
w)
handle e :: Event
e@(CrossingEvent {ev_event_type :: Event -> EventType
ev_event_type = EventType
t})
| EventType
t EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
leaveNotify
= do KeySym
rootw <- (XConf -> KeySym) -> X KeySym
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> KeySym
theRoot
Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Event -> KeySym
ev_window Event
e KeySym -> KeySym -> Bool
forall a. Eq a => a -> a -> Bool
== KeySym
rootw Bool -> Bool -> Bool
&& Bool -> Bool
not (Event -> Bool
ev_same_screen Event
e)) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ KeySym -> X ()
setFocusX KeySym
rootw
handle e :: Event
e@(ConfigureRequestEvent {ev_window :: Event -> KeySym
ev_window = KeySym
w}) = (Display -> X ()) -> X ()
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X ()) -> X ()) -> (Display -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Display
dpy -> do
WindowSet
ws <- (XState -> WindowSet) -> X WindowSet
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
EventType
bw <- (XConf -> EventType) -> X EventType
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> EventType
forall (l :: * -> *). XConfig l -> EventType
borderWidth (XConfig Layout -> EventType)
-> (XConf -> XConfig Layout) -> XConf -> EventType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config)
if KeySym -> Map KeySym RationalRect -> Bool
forall k a. Ord k => k -> Map k a -> Bool
M.member KeySym
w (WindowSet -> Map KeySym RationalRect
forall i l a sid sd. StackSet i l a sid sd -> Map a RationalRect
floating WindowSet
ws)
Bool -> Bool -> Bool
|| Bool -> Bool
not (KeySym -> WindowSet -> Bool
forall a i l s sd. Eq a => a -> StackSet i l a s sd -> Bool
member KeySym
w WindowSet
ws)
then do IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display -> KeySym -> CULong -> WindowChanges -> IO ()
configureWindow Display
dpy KeySym
w (Event -> CULong
ev_value_mask Event
e) (WindowChanges -> IO ()) -> WindowChanges -> IO ()
forall a b. (a -> b) -> a -> b
$ WindowChanges
{ wc_x :: CInt
wc_x = Event -> CInt
ev_x Event
e
, wc_y :: CInt
wc_y = Event -> CInt
ev_y Event
e
, wc_width :: CInt
wc_width = Event -> CInt
ev_width Event
e
, wc_height :: CInt
wc_height = Event -> CInt
ev_height Event
e
, wc_border_width :: CInt
wc_border_width = EventType -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral EventType
bw
, wc_sibling :: KeySym
wc_sibling = Event -> KeySym
ev_above Event
e
, wc_stack_mode :: CInt
wc_stack_mode = Event -> CInt
ev_detail Event
e }
Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (KeySym -> WindowSet -> Bool
forall a i l s sd. Eq a => a -> StackSet i l a s sd -> Bool
member KeySym
w WindowSet
ws) (KeySym -> X ()
float KeySym
w)
else Display -> KeySym -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes Display
dpy KeySym
w ((WindowAttributes -> X ()) -> X ())
-> (WindowAttributes -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \WindowAttributes
wa -> IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ (XEventPtr -> IO ()) -> IO ()
forall a. (XEventPtr -> IO a) -> IO a
allocaXEvent ((XEventPtr -> IO ()) -> IO ()) -> (XEventPtr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \XEventPtr
ev -> do
XEventPtr -> EventType -> IO ()
setEventType XEventPtr
ev EventType
configureNotify
XEventPtr
-> KeySym
-> KeySym
-> CInt
-> CInt
-> CInt
-> CInt
-> CInt
-> KeySym
-> Bool
-> IO ()
setConfigureEvent XEventPtr
ev KeySym
w KeySym
w
(WindowAttributes -> CInt
wa_x WindowAttributes
wa) (WindowAttributes -> CInt
wa_y WindowAttributes
wa) (WindowAttributes -> CInt
wa_width WindowAttributes
wa)
(WindowAttributes -> CInt
wa_height WindowAttributes
wa) (Event -> CInt
ev_border_width Event
e) KeySym
none (WindowAttributes -> Bool
wa_override_redirect WindowAttributes
wa)
Display -> KeySym -> Bool -> KeySym -> XEventPtr -> IO ()
sendEvent Display
dpy KeySym
w Bool
False KeySym
0 XEventPtr
ev
IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display -> Bool -> IO ()
sync Display
dpy Bool
False
handle (ConfigureEvent {ev_window :: Event -> KeySym
ev_window = KeySym
w}) = X Bool -> X () -> X ()
whenX (KeySym -> X Bool
isRoot KeySym
w) X ()
rescreen
handle event :: Event
event@(PropertyEvent { ev_event_type :: Event -> EventType
ev_event_type = EventType
t, ev_atom :: Event -> KeySym
ev_atom = KeySym
a })
| EventType
t EventType -> EventType -> Bool
forall a. Eq a => a -> a -> Bool
== EventType
propertyNotify Bool -> Bool -> Bool
&& KeySym
a KeySym -> KeySym -> Bool
forall a. Eq a => a -> a -> Bool
== KeySym
wM_NAME = (XConf -> X ()) -> X (X ())
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> X ()
forall (l :: * -> *). XConfig l -> X ()
logHook (XConfig Layout -> X ())
-> (XConf -> XConfig Layout) -> XConf -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config) X (X ()) -> (X () -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= () -> X () -> X ()
forall a. a -> X a -> X a
userCodeDef () X () -> X () -> X ()
forall a b. X a -> X b -> X b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Event -> X ()
forall a. Message a => a -> X ()
broadcastMessage Event
event
handle e :: Event
e@ClientMessageEvent { ev_message_type :: Event -> KeySym
ev_message_type = KeySym
mt } = do
KeySym
a <- String -> X KeySym
getAtom String
"XMONAD_RESTART"
if KeySym
mt KeySym -> KeySym -> Bool
forall a. Eq a => a -> a -> Bool
== KeySym
a
then String -> Bool -> X ()
restart String
"xmonad" Bool
True
else Event -> X ()
forall a. Message a => a -> X ()
broadcastMessage Event
e
handle Event
e = Event -> X ()
forall a. Message a => a -> X ()
broadcastMessage Event
e
scan :: Display -> Window -> IO [Window]
scan :: Display -> KeySym -> IO [KeySym]
scan Display
dpy KeySym
rootw = do
(KeySym
_, KeySym
_, [KeySym]
ws) <- Display -> KeySym -> IO (KeySym, KeySym, [KeySym])
queryTree Display
dpy KeySym
rootw
(KeySym -> IO Bool) -> [KeySym] -> IO [KeySym]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (\KeySym
w -> KeySym -> IO Bool
ok KeySym
w IO Bool -> (SomeException -> IO Bool) -> IO Bool
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` SomeException -> IO Bool
skip) [KeySym]
ws
where ok :: KeySym -> IO Bool
ok KeySym
w = do WindowAttributes
wa <- Display -> KeySym -> IO WindowAttributes
getWindowAttributes Display
dpy KeySym
w
KeySym
a <- Display -> String -> Bool -> IO KeySym
internAtom Display
dpy String
"WM_STATE" Bool
False
Maybe [CLong]
p <- Display -> KeySym -> KeySym -> IO (Maybe [CLong])
getWindowProperty32 Display
dpy KeySym
a KeySym
w
let ic :: Bool
ic = case Maybe [CLong]
p of
Just (CLong
3:[CLong]
_) -> Bool
True
Maybe [CLong]
_ -> Bool
False
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (WindowAttributes -> Bool
wa_override_redirect WindowAttributes
wa)
Bool -> Bool -> Bool
&& (WindowAttributes -> CInt
wa_map_state WindowAttributes
wa CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
waIsViewable Bool -> Bool -> Bool
|| Bool
ic)
skip :: E.SomeException -> IO Bool
skip :: SomeException -> IO Bool
skip SomeException
_ = Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
grabKeys :: X ()
grabKeys :: X ()
grabKeys = do
XConf { display :: XConf -> Display
display = Display
dpy, theRoot :: XConf -> KeySym
theRoot = KeySym
rootw } <- X XConf
forall r (m :: * -> *). MonadReader r m => m r
ask
IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display -> KeyCode -> ButtonMask -> KeySym -> IO ()
ungrabKey Display
dpy KeyCode
anyKey ButtonMask
anyModifier KeySym
rootw
let grab :: (KeyMask, KeyCode) -> X ()
grab :: (ButtonMask, KeyCode) -> X ()
grab (ButtonMask
km, KeyCode
kc) = IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display
-> KeyCode -> ButtonMask -> KeySym -> Bool -> CInt -> CInt -> IO ()
grabKey Display
dpy KeyCode
kc ButtonMask
km KeySym
rootw Bool
True CInt
grabModeAsync CInt
grabModeAsync
((ButtonMask, KeyCode) -> X ()) -> [(ButtonMask, KeyCode)] -> X ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (ButtonMask, KeyCode) -> X ()
grab ([(ButtonMask, KeyCode)] -> X ())
-> X [(ButtonMask, KeyCode)] -> X ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(ButtonMask, KeySym)] -> X [(ButtonMask, KeyCode)]
mkGrabs ([(ButtonMask, KeySym)] -> X [(ButtonMask, KeyCode)])
-> X [(ButtonMask, KeySym)] -> X [(ButtonMask, KeyCode)]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (XConf -> [(ButtonMask, KeySym)]) -> X [(ButtonMask, KeySym)]
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Map (ButtonMask, KeySym) (X ()) -> [(ButtonMask, KeySym)]
forall k a. Map k a -> [k]
M.keys (Map (ButtonMask, KeySym) (X ()) -> [(ButtonMask, KeySym)])
-> (XConf -> Map (ButtonMask, KeySym) (X ()))
-> XConf
-> [(ButtonMask, KeySym)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> Map (ButtonMask, KeySym) (X ())
keyActions)
grabButtons :: X ()
grabButtons :: X ()
grabButtons = do
XConf { display :: XConf -> Display
display = Display
dpy, theRoot :: XConf -> KeySym
theRoot = KeySym
rootw } <- X XConf
forall r (m :: * -> *). MonadReader r m => m r
ask
let grab :: EventType -> ButtonMask -> m ()
grab EventType
button ButtonMask
mask = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Display
-> EventType
-> ButtonMask
-> KeySym
-> Bool
-> KeySym
-> CInt
-> CInt
-> KeySym
-> KeySym
-> IO ()
grabButton Display
dpy EventType
button ButtonMask
mask KeySym
rootw Bool
False KeySym
buttonPressMask
CInt
grabModeAsync CInt
grabModeSync KeySym
none KeySym
none
IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display -> EventType -> ButtonMask -> KeySym -> IO ()
ungrabButton Display
dpy EventType
anyButton ButtonMask
anyModifier KeySym
rootw
[ButtonMask]
ems <- X [ButtonMask]
extraModifiers
Map (ButtonMask, EventType) (KeySym -> X ())
ba <- (XConf -> Map (ButtonMask, EventType) (KeySym -> X ()))
-> X (Map (ButtonMask, EventType) (KeySym -> X ()))
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Map (ButtonMask, EventType) (KeySym -> X ())
buttonActions
((ButtonMask, EventType) -> X ())
-> [(ButtonMask, EventType)] -> X ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(ButtonMask
m,EventType
b) -> (ButtonMask -> X ()) -> [ButtonMask] -> X ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (EventType -> ButtonMask -> X ()
forall {m :: * -> *}. MonadIO m => EventType -> ButtonMask -> m ()
grab EventType
b (ButtonMask -> X ())
-> (ButtonMask -> ButtonMask) -> ButtonMask -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ButtonMask
m ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|.)) [ButtonMask]
ems) (Map (ButtonMask, EventType) (KeySym -> X ())
-> [(ButtonMask, EventType)]
forall k a. Map k a -> [k]
M.keys Map (ButtonMask, EventType) (KeySym -> X ())
ba)