A.FloatSnap snap to unmanaged docks too

This commit is contained in:
Adam Vogt 2009-05-25 00:18:34 +00:00
parent 6703453f26
commit 49bb2655ff
2 changed files with 16 additions and 4 deletions

View File

@ -24,11 +24,13 @@ module XMonad.Actions.FloatSnap (
snapMagicMouseResize) where snapMagicMouseResize) where
import XMonad import XMonad
import Control.Monad(filterM)
import Control.Applicative((<$>))
import Data.List (sort) import Data.List (sort)
import Data.Maybe (listToMaybe,fromJust,isNothing) import Data.Maybe (listToMaybe,fromJust,isNothing)
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.Hooks.ManageDocks (Direction(..)) import XMonad.Hooks.ManageDocks (Direction(..),getStrut)
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@ -274,9 +276,10 @@ snapResize grow dir collidedist w = whenX (isClient w) $ withDisplay $ \d -> do
getSnap :: Bool -> Maybe Int -> Display -> Window -> X ((Maybe Int,Maybe Int,Bool),(Maybe Int,Maybe Int,Bool)) getSnap :: Bool -> Maybe Int -> Display -> Window -> X ((Maybe Int,Maybe Int,Bool),(Maybe Int,Maybe Int,Bool))
getSnap horiz collidedist d w = do getSnap horiz collidedist d w = do
wa <- io $ getWindowAttributes d w wa <- io $ getWindowAttributes d w
screen <- W.current `fmap` gets windowset screen <- W.current <$> gets windowset
unManaged <- unManagedDocks
let sr = screenRect $ W.screenDetail screen let sr = screenRect $ W.screenDetail screen
wl = W.integrate' $ W.stack $ W.workspace screen wl = (unManaged ++) . W.integrate' . W.stack $ W.workspace screen
wla <- filter (collides wa) `fmap` (io $ mapM (getWindowAttributes d) $ filter (/=w) wl) wla <- filter (collides wa) `fmap` (io $ mapM (getWindowAttributes d) $ filter (/=w) wl)
return ( neighbours (back wa sr wla) (wpos wa) return ( neighbours (back wa sr wla) (wpos wa)
@ -307,6 +310,12 @@ getSnap horiz collidedist d w = do
Just dist -> ( refwpos oa - wborder oa < refwpos wa + refwdim wa + wborder wa + dist Just dist -> ( refwpos oa - wborder oa < refwpos wa + refwdim wa + wborder wa + dist
&& refwpos wa - wborder wa - dist < refwpos oa + refwdim oa + wborder oa ) && refwpos wa - wborder wa - dist < refwpos oa + refwdim oa + wborder oa )
unManagedDocks :: X [Window]
unManagedDocks = withWindowSet $ \ws -> withDisplay $ \disp ->
fmap (filter (`notElem` W.allWindows ws)) .
filterM (fmap (not . null) . getStrut) . (\(_,_,x) -> x)
=<< io . queryTree disp
=<< asks theRoot
constructors :: Bool -> (WindowAttributes -> Int, WindowAttributes -> Int, Rectangle -> Int, Rectangle -> Int) constructors :: Bool -> (WindowAttributes -> Int, WindowAttributes -> Int, Rectangle -> Int, Rectangle -> Int)
constructors True = ( fromIntegral.wa_x constructors True = ( fromIntegral.wa_x

View File

@ -18,7 +18,10 @@ module XMonad.Hooks.ManageDocks (
-- * Usage -- * Usage
-- $usage -- $usage
manageDocks, checkDock, AvoidStruts, avoidStruts, avoidStrutsOn, manageDocks, checkDock, AvoidStruts, avoidStruts, avoidStrutsOn,
ToggleStruts(..), Direction(..) ToggleStruts(..), Direction(..),
-- for XMonad.Actions.FloatSnap
getStrut
) where ) where