{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
module XMonad.Operations where
import XMonad.Core
import XMonad.Layout (Full(..))
import qualified XMonad.StackSet as W
import Data.Maybe
import Data.Monoid (Endo(..),Any(..))
import Data.List (nub, (\\), find)
import Data.Bits ((.|.), (.&.), complement, testBit)
import Data.Ratio
import qualified Data.Map as M
import qualified Data.Set as S
import Control.Applicative((<$>), (<*>))
import Control.Arrow (second)
import Control.Monad (void)
import Control.Monad.Reader
import Control.Monad.State
import qualified Control.Exception.Extensible as C
import System.IO
import System.Directory
import System.Posix.Process (executeFile)
import Graphics.X11.Xlib
import Graphics.X11.Xinerama (getScreenInfo)
import Graphics.X11.Xlib.Extras
manage :: Window -> X ()
manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
sh <- io $ getWMNormalHints d w
let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
isTransient <- isJust <$> io (getTransientForHint d w)
rr <- snd `fmap` floatLocation w
let adjust (W.RationalRect x y wid h) | x + wid > 1 || y + h > 1 || x < 0 || y < 0
= W.RationalRect (0.5 - wid/2) (0.5 - h/2) wid h
adjust r = r
f ws | isFixedSize || isTransient = W.float w (adjust rr) . W.insertUp w . W.view i $ ws
| otherwise = W.insertUp w ws
where i = W.tag $ W.workspace $ W.current ws
mh <- asks (manageHook . config)
g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
windows (g . f)
unmanage :: Window -> X ()
unmanage = windows . W.delete
killWindow :: Window -> X ()
killWindow w = withDisplay $ \d -> do
wmdelt <- atom_WM_DELETE_WINDOW ; wmprot <- atom_WM_PROTOCOLS
protocols <- io $ getWMProtocols d w
io $ if wmdelt `elem` protocols
then allocaXEvent $ \ev -> do
setEventType ev clientMessage
setClientMessageEvent ev w wmprot 32 wmdelt 0
sendEvent d w False noEventMask ev
else killClient d w >> return ()
kill :: X ()
kill = withFocused killWindow
windows :: (WindowSet -> WindowSet) -> X ()
windows f = do
XState { windowset = old } <- get
let oldvisible = concatMap (W.integrate' . W.stack . W.workspace) $ W.current old : W.visible old
newwindows = W.allWindows ws \\ W.allWindows old
ws = f old
XConf { display = d , normalBorder = nbc, focusedBorder = fbc } <- ask
mapM_ setInitialProperties newwindows
whenJust (W.peek old) $ \otherw -> do
nbs <- asks (normalBorderColor . config)
setWindowBorderWithFallback d otherw nbs nbc
modify (\s -> s { windowset = ws })
let tags_oldvisible = map (W.tag . W.workspace) $ W.current old : W.visible old
gottenhidden = filter (flip elem tags_oldvisible . W.tag) $ W.hidden ws
mapM_ (sendMessageWithNoRefresh Hide) gottenhidden
let allscreens = W.screens ws
summed_visible = scanl (++) [] $ map (W.integrate' . W.stack . W.workspace) allscreens
rects <- fmap concat $ forM (zip allscreens summed_visible) $ \ (w, vis) -> do
let wsp = W.workspace w
this = W.view n ws
n = W.tag wsp
tiled = (W.stack . W.workspace . W.current $ this)
>>= W.filter (`M.notMember` W.floating ws)
>>= W.filter (`notElem` vis)
viewrect = screenRect $ W.screenDetail w
(rs, ml') <- runLayout wsp { W.stack = tiled } viewrect `catchX`
runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
updateLayout n ml'
let m = W.floating ws
flt = [(fw, scaleRationalRect viewrect r)
| fw <- filter (flip M.member m) (W.index this)
, Just r <- [M.lookup fw m]]
vs = flt ++ rs
io $ restackWindows d (map fst vs)
return vs
let visible = map fst rects
mapM_ (uncurry tileWindow) rects
whenJust (W.peek ws) $ \w -> do
fbs <- asks (focusedBorderColor . config)
setWindowBorderWithFallback d w fbs fbc
mapM_ reveal visible
setTopFocus
mapM_ hide (nub (oldvisible ++ newwindows) \\ visible)
mapM_ (flip setWMState withdrawnState) (W.allWindows old \\ W.allWindows ws)
isMouseFocused <- asks mouseFocused
unless isMouseFocused $ clearEvents enterWindowMask
asks (logHook . config) >>= userCodeDef ()
modifyWindowSet :: (WindowSet -> WindowSet) -> X ()
modifyWindowSet f = modify $ \xst -> xst { windowset = f (windowset xst) }
windowBracket :: (a -> Bool) -> X a -> X a
windowBracket p action = withWindowSet $ \old -> do
a <- action
when (p a) . withWindowSet $ \new -> do
modifyWindowSet $ \_ -> old
windows $ \_ -> new
return a
windowBracket_ :: X Any -> X ()
windowBracket_ = void . windowBracket getAny
scaleRationalRect :: Rectangle -> W.RationalRect -> Rectangle
scaleRationalRect (Rectangle sx sy sw sh) (W.RationalRect rx ry rw rh)
= Rectangle (sx + scale sw rx) (sy + scale sh ry) (scale sw rw) (scale sh rh)
where scale s r = floor (toRational s * r)
setWMState :: Window -> Int -> X ()
setWMState w v = withDisplay $ \dpy -> do
a <- atom_WM_STATE
io $ changeProperty32 dpy w a a propModeReplace [fromIntegral v, fromIntegral none]
setWindowBorderWithFallback :: Display -> Window -> String -> Pixel -> X ()
setWindowBorderWithFallback dpy w color basic = io $
C.handle fallback $ do
wa <- getWindowAttributes dpy w
pixel <- color_pixel . fst <$> allocNamedColor dpy (wa_colormap wa) color
setWindowBorder dpy w pixel
where
fallback :: C.SomeException -> IO ()
fallback e = do hPrint stderr e >> hFlush stderr
setWindowBorder dpy w basic
hide :: Window -> X ()
hide w = whenX (gets (S.member w . mapped)) $ withDisplay $ \d -> do
cMask <- asks $ clientMask . config
io $ do selectInput d w (cMask .&. complement structureNotifyMask)
unmapWindow d w
selectInput d w cMask
setWMState w iconicState
modify (\s -> s { waitingUnmap = M.insertWith (+) w 1 (waitingUnmap s)
, mapped = S.delete w (mapped s) })
reveal :: Window -> X ()
reveal w = withDisplay $ \d -> do
setWMState w normalState
io $ mapWindow d w
whenX (isClient w) $ modify (\s -> s { mapped = S.insert w (mapped s) })
setInitialProperties :: Window -> X ()
setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
setWMState w iconicState
asks (clientMask . config) >>= io . selectInput d w
bw <- asks (borderWidth . config)
io $ setWindowBorderWidth d w bw
io $ setWindowBorder d w nb
refresh :: X ()
refresh = windows id
clearEvents :: EventMask -> X ()
clearEvents mask = withDisplay $ \d -> io $ do
sync d False
allocaXEvent $ \p -> fix $ \again -> do
more <- checkMaskEvent d mask p
when more again
tileWindow :: Window -> Rectangle -> X ()
tileWindow w r = withDisplay $ \d -> withWindowAttributes d w $ \wa -> do
let bw = fromIntegral $ wa_border_width wa
least x | x <= bw*2 = 1
| otherwise = x - bw*2
io $ moveResizeWindow d w (rect_x r) (rect_y r)
(least $ rect_width r) (least $ rect_height r)
containedIn :: Rectangle -> Rectangle -> Bool
containedIn r1@(Rectangle x1 y1 w1 h1) r2@(Rectangle x2 y2 w2 h2)
= and [ r1 /= r2
, x1 >= x2
, y1 >= y2
, fromIntegral x1 + w1 <= fromIntegral x2 + w2
, fromIntegral y1 + h1 <= fromIntegral y2 + h2 ]
nubScreens :: [Rectangle] -> [Rectangle]
nubScreens xs = nub . filter (\x -> not $ any (x `containedIn`) xs) $ xs
getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle]
getCleanedScreenInfo = io . fmap nubScreens . getScreenInfo
rescreen :: X ()
rescreen = do
xinesc <- withDisplay getCleanedScreenInfo
windows $ \ws@(W.StackSet { W.current = v, W.visible = vs, W.hidden = hs }) ->
let (xs, ys) = splitAt (length xinesc) $ map W.workspace (v:vs) ++ hs
(a:as) = zipWith3 W.Screen xs [0..] $ map SD xinesc
in ws { W.current = a
, W.visible = as
, W.hidden = ys }
setButtonGrab :: Bool -> Window -> X ()
setButtonGrab grab w = do
pointerMode <- asks $ \c -> if clickJustFocuses (config c)
then grabModeAsync
else grabModeSync
withDisplay $ \d -> io $ if grab
then forM_ [button1, button2, button3] $ \b ->
grabButton d b anyModifier w False buttonPressMask
pointerMode grabModeSync none none
else ungrabButton d anyButton anyModifier w
setTopFocus :: X ()
setTopFocus = withWindowSet $ maybe (setFocusX =<< asks theRoot) setFocusX . W.peek
focus :: Window -> X ()
focus w = local (\c -> c { mouseFocused = True }) $ withWindowSet $ \s -> do
let stag = W.tag . W.workspace
curr = stag $ W.current s
mnew <- maybe (return Nothing) (fmap (fmap stag) . uncurry pointScreen)
=<< asks mousePosition
root <- asks theRoot
case () of
_ | W.member w s && W.peek s /= Just w -> windows (W.focusWindow w)
| Just new <- mnew, w == root && curr /= new
-> windows (W.view new)
| otherwise -> return ()
setFocusX :: Window -> X ()
setFocusX w = withWindowSet $ \ws -> do
dpy <- asks display
forM_ (W.current ws : W.visible ws) $ \wk ->
forM_ (W.index (W.view (W.tag (W.workspace wk)) ws)) $ \otherw ->
setButtonGrab True otherw
whenX (not <$> isRoot w) $ setButtonGrab False w
hints <- io $ getWMHints dpy w
protocols <- io $ getWMProtocols dpy w
wmprot <- atom_WM_PROTOCOLS
wmtf <- atom_WM_TAKE_FOCUS
currevt <- asks currentEvent
let inputHintSet = wmh_flags hints `testBit` inputHintBit
when ((inputHintSet && wmh_input hints) || (not inputHintSet)) $
io $ do setInputFocus dpy w revertToPointerRoot 0
when (wmtf `elem` protocols) $
io $ allocaXEvent $ \ev -> do
setEventType ev clientMessage
setClientMessageEvent ev w wmprot 32 wmtf $ maybe currentTime event_time currevt
sendEvent dpy w False noEventMask ev
where event_time ev =
if (ev_event_type ev) `elem` timedEvents then
ev_time ev
else
currentTime
timedEvents = [ keyPress, keyRelease, buttonPress, buttonRelease, enterNotify, leaveNotify, selectionRequest ]
sendMessage :: Message a => a -> X ()
sendMessage a = windowBracket_ $ do
w <- W.workspace . W.current <$> gets windowset
ml' <- handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing
whenJust ml' $ \l' ->
modifyWindowSet $ \ws -> ws { W.current = (W.current ws)
{ W.workspace = (W.workspace $ W.current ws)
{ W.layout = l' }}}
return (Any $ isJust ml')
broadcastMessage :: Message a => a -> X ()
broadcastMessage a = withWindowSet $ \ws -> do
let c = W.workspace . W.current $ ws
v = map W.workspace . W.visible $ ws
h = W.hidden ws
mapM_ (sendMessageWithNoRefresh a) (c : v ++ h)
sendMessageWithNoRefresh :: Message a => a -> W.Workspace WorkspaceId (Layout Window) Window -> X ()
sendMessageWithNoRefresh a w =
handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
updateLayout (W.tag w)
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
updateLayout i ml = whenJust ml $ \l ->
runOnWorkspaces $ \ww -> return $ if W.tag ww == i then ww { W.layout = l} else ww
setLayout :: Layout Window -> X ()
setLayout l = do
ss@(W.StackSet { W.current = c@(W.Screen { W.workspace = ws })}) <- gets windowset
handleMessage (W.layout ws) (SomeMessage ReleaseResources)
windows $ const $ ss {W.current = c { W.workspace = ws { W.layout = l } } }
screenWorkspace :: ScreenId -> X (Maybe WorkspaceId)
screenWorkspace sc = withWindowSet $ return . W.lookupWorkspace sc
withFocused :: (Window -> X ()) -> X ()
withFocused f = withWindowSet $ \w -> whenJust (W.peek w) f
isClient :: Window -> X Bool
isClient w = withWindowSet $ return . W.member w
extraModifiers :: X [KeyMask]
extraModifiers = do
nlm <- gets numberlockMask
return [0, nlm, lockMask, nlm .|. lockMask ]
cleanMask :: KeyMask -> X KeyMask
cleanMask km = do
nlm <- gets numberlockMask
return (complement (nlm .|. lockMask) .&. km)
initColor :: Display -> String -> IO (Maybe Pixel)
initColor dpy c = C.handle (\(C.SomeException _) -> return Nothing) $
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
where colormap = defaultColormap dpy (defaultScreen dpy)
data StateFile = StateFile
{ sfWins :: W.StackSet WorkspaceId String Window ScreenId ScreenDetail
, sfExt :: [(String, String)]
} deriving (Show, Read)
writeStateToFile :: X ()
writeStateToFile = do
let maybeShow (t, Right (PersistentExtension ext)) = Just (t, show ext)
maybeShow (t, Left str) = Just (t, str)
maybeShow _ = Nothing
wsData = W.mapLayout show . windowset
extState = catMaybes . map maybeShow . M.toList . extensibleState
path <- stateFileName
stateData <- gets (\s -> StateFile (wsData s) (extState s))
catchIO (writeFile path $ show stateData)
readStateFile :: (LayoutClass l Window, Read (l Window)) => XConfig l -> X (Maybe XState)
readStateFile xmc = do
path <- stateFileName
sf' <- userCode . io $ do
raw <- withFile path ReadMode readStrict
return $! maybeRead reads raw
io (removeFile path)
return $ do
sf <- join sf'
let winset = W.ensureTags layout (workspaces xmc) $ W.mapLayout (fromMaybe layout . maybeRead lreads) (sfWins sf)
extState = M.fromList . map (second Left) $ sfExt sf
return XState { windowset = winset
, numberlockMask = 0
, mapped = S.empty
, waitingUnmap = M.empty
, dragging = Nothing
, extensibleState = extState
}
where
layout = Layout (layoutHook xmc)
lreads = readsLayout layout
maybeRead reads' s = case reads' s of
[(x, "")] -> Just x
_ -> Nothing
readStrict :: Handle -> IO String
readStrict h = hGetContents h >>= \s -> length s `seq` return s
{-# DEPRECATED migrateState "will be removed some point in the future." #-}
migrateState :: (Functor m, MonadIO m) => String -> String -> m ()
migrateState ws xs = do
io (putStrLn "WARNING: --resume is no longer supported.")
whenJust stateData $ \s -> do
path <- stateFileName
catchIO (writeFile path $ show s)
where
stateData = StateFile <$> maybeRead ws <*> maybeRead xs
maybeRead s = case reads s of
[(x, "")] -> Just x
_ -> Nothing
restart :: String -> Bool -> X ()
restart prog resume = do
broadcastMessage ReleaseResources
io . flush =<< asks display
when resume writeStateToFile
catchIO (executeFile prog True [] Nothing)
floatLocation :: Window -> X (ScreenId, W.RationalRect)
floatLocation w =
catchX go $ do
sc <- W.current <$> gets windowset
return (W.screen sc, W.RationalRect 0 0 1 1)
where fi x = fromIntegral x
go = withDisplay $ \d -> do
ws <- gets windowset
wa <- io $ getWindowAttributes d w
let bw = (fromIntegral . wa_border_width) wa
sc <- fromMaybe (W.current ws) <$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
let sr = screenRect . W.screenDetail $ sc
rr = W.RationalRect ((fi (wa_x wa) - fi (rect_x sr)) % fi (rect_width sr))
((fi (wa_y wa) - fi (rect_y sr)) % fi (rect_height sr))
(fi (wa_width wa + bw*2) % fi (rect_width sr))
(fi (wa_height wa + bw*2) % fi (rect_height sr))
return (W.screen sc, rr)
pointScreen :: Position -> Position
-> X (Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail))
pointScreen x y = withWindowSet $ return . find p . W.screens
where p = pointWithin x y . screenRect . W.screenDetail
pointWithin :: Position -> Position -> Rectangle -> Bool
pointWithin x y r = x >= rect_x r &&
x < rect_x r + fromIntegral (rect_width r) &&
y >= rect_y r &&
y < rect_y r + fromIntegral (rect_height r)
float :: Window -> X ()
float w = do
(sc, rr) <- floatLocation w
windows $ \ws -> W.float w rr . fromMaybe ws $ do
i <- W.findTag w ws
guard $ i `elem` map (W.tag . W.workspace) (W.screens ws)
f <- W.peek ws
sw <- W.lookupWorkspace sc ws
return (W.focusWindow f . W.shiftWin sw w $ ws)
mouseDrag :: (Position -> Position -> X ()) -> X () -> X ()
mouseDrag f done = do
drag <- gets dragging
case drag of
Just _ -> return ()
Nothing -> do
XConf { theRoot = root, display = d } <- ask
io $ grabPointer d root False (buttonReleaseMask .|. pointerMotionMask)
grabModeAsync grabModeAsync none none currentTime
modify $ \s -> s { dragging = Just (motion, cleanup) }
where
cleanup = do
withDisplay $ io . flip ungrabPointer currentTime
modify $ \s -> s { dragging = Nothing }
done
motion x y = do z <- f x y
clearEvents pointerMotionMask
return z
mouseMoveWindow :: Window -> X ()
mouseMoveWindow w = whenX (isClient w) $ withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
(_, _, _, ox', oy', _, _, _) <- io $ queryPointer d w
let ox = fromIntegral ox'
oy = fromIntegral oy'
mouseDrag (\ex ey -> do
io $ moveWindow d w (fromIntegral (fromIntegral (wa_x wa) + (ex - ox)))
(fromIntegral (fromIntegral (wa_y wa) + (ey - oy)))
float w
)
(float w)
mouseResizeWindow :: Window -> X ()
mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
sh <- io $ getWMNormalHints d w
io $ warpPointer d none w 0 0 0 0 (fromIntegral (wa_width wa)) (fromIntegral (wa_height wa))
mouseDrag (\ex ey -> do
io $ resizeWindow d w `uncurry`
applySizeHintsContents sh (ex - fromIntegral (wa_x wa),
ey - fromIntegral (wa_y wa))
float w)
(float w)
type D = (Dimension, Dimension)
mkAdjust :: Window -> X (D -> D)
mkAdjust w = withDisplay $ \d -> liftIO $ do
sh <- getWMNormalHints d w
wa <- C.try $ getWindowAttributes d w
case wa of
Left err -> const (return id) (err :: C.SomeException)
Right wa' ->
let bw = fromIntegral $ wa_border_width wa'
in return $ applySizeHints bw sh
applySizeHints :: Integral a => Dimension -> SizeHints -> (a, a) -> D
applySizeHints bw sh =
tmap (+ 2 * bw) . applySizeHintsContents sh . tmap (subtract $ 2 * fromIntegral bw)
where
tmap f (x, y) = (f x, f y)
applySizeHintsContents :: Integral a => SizeHints -> (a, a) -> D
applySizeHintsContents sh (w, h) =
applySizeHints' sh (fromIntegral $ max 1 w, fromIntegral $ max 1 h)
applySizeHints' :: SizeHints -> D -> D
applySizeHints' sh =
maybe id applyMaxSizeHint (sh_max_size sh)
. maybe id (\(bw, bh) (w, h) -> (w+bw, h+bh)) (sh_base_size sh)
. maybe id applyResizeIncHint (sh_resize_inc sh)
. maybe id applyAspectHint (sh_aspect sh)
. maybe id (\(bw,bh) (w,h) -> (w-bw, h-bh)) (sh_base_size sh)
applyAspectHint :: (D, D) -> D -> D
applyAspectHint ((minx, miny), (maxx, maxy)) x@(w,h)
| or [minx < 1, miny < 1, maxx < 1, maxy < 1] = x
| w * maxy > h * maxx = (h * maxx `div` maxy, h)
| w * miny < h * minx = (w, w * miny `div` minx)
| otherwise = x
applyResizeIncHint :: D -> D -> D
applyResizeIncHint (iw,ih) x@(w,h) =
if iw > 0 && ih > 0 then (w - w `mod` iw, h - h `mod` ih) else x
applyMaxSizeHint :: D -> D -> D
applyMaxSizeHint (mw,mh) x@(w,h) =
if mw > 0 && mh > 0 then (min w mw,min h mh) else x