summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMatthias Schiffer <mschiffer@universe-factory.net>2013-09-09 02:18:28 +0200
committerMatthias Schiffer <mschiffer@universe-factory.net>2013-09-09 02:18:28 +0200
commitc4630dfd41c7ee2bdb2cc9f75a139b51e28ea9e4 (patch)
treec023b9b853db82cf499204d9638108e649060613
parent5b87ecbe82f6b979069ebf26dc8b3357867bea8b (diff)
downloadmetatile-c4630dfd41c7ee2bdb2cc9f75a139b51e28ea9e4.tar
metatile-c4630dfd41c7ee2bdb2cc9f75a139b51e28ea9e4.zip
Remove concept of floating windows
They will be re-introduced later as a layout modifier
-rw-r--r--XMonad/Config.hs18
-rw-r--r--XMonad/Main.hsc6
-rw-r--r--XMonad/ManageHook.hs6
-rw-r--r--XMonad/Operations.hs38
-rw-r--r--XMonad/StackSet.hs27
5 files changed, 25 insertions, 70 deletions
diff --git a/XMonad/Config.hs b/XMonad/Config.hs
index 9aaab8f..ed931b2 100644
--- a/XMonad/Config.hs
+++ b/XMonad/Config.hs
@@ -36,7 +36,6 @@ import qualified XMonad.Core as XMonad
import XMonad.Layout
import XMonad.Operations
-import XMonad.ManageHook
import qualified XMonad.StackSet as W
import Data.Bits ((.|.))
import Data.Default
@@ -90,9 +89,7 @@ focusedBorderColor = "red" -- "#ff0000" don't use hex, not <24 bit safe
-- and click on the client you're interested in.
--
manageHook :: ManageHook
-manageHook = composeAll
- [ className =? "MPlayer" --> doFloat
- , className =? "Gimp" --> doFloat ]
+manageHook = mempty
------------------------------------------------------------------------
-- Logging
@@ -210,9 +207,6 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
, ((modMask, xK_h ), sendMessage Shrink) -- %! Shrink the master area
, ((modMask, xK_l ), sendMessage Expand) -- %! Expand the master area
- -- floating layer support
- , ((modMask, xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling
-
-- increase or decrease number of windows in the master area
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
, ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
@@ -241,14 +235,8 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
-- | Mouse bindings: default actions bound to mouse events
mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList
- -- mod-button1 %! Set the window to floating mode and move by dragging
- [ ((modMask, button1), \w -> focus w >> mouseMoveWindow w
- >> windows W.shiftMaster)
-- mod-button2 %! Raise the window to the top of the stack
- , ((modMask, button2), windows . (W.shiftMaster .) . W.focusWindow)
- -- mod-button3 %! Set the window to floating mode and resize by dragging
- , ((modMask, button3), \w -> focus w >> mouseResizeWindow w
- >> windows W.shiftMaster)
+ [ ((modMask, button2), windows . (W.shiftMaster .) . W.focusWindow)
-- you may also bind events to the mouse scroll wheel (button4 and button5)
]
@@ -327,4 +315,4 @@ help = unlines ["The default modifier key is 'alt'. Default keybindings:",
"-- Mouse bindings: default actions bound to mouse events",
"mod-button1 Set the window to floating mode and move by dragging",
"mod-button2 Raise the window to the top of the stack",
- "mod-button3 Set the window to floating mode and resize by dragging"] \ No newline at end of file
+ "mod-button3 Set the window to floating mode and resize by dragging"]
diff --git a/XMonad/Main.hsc b/XMonad/Main.hsc
index 75cb94c..c038ecb 100644
--- a/XMonad/Main.hsc
+++ b/XMonad/Main.hsc
@@ -36,7 +36,7 @@ import Graphics.X11.Xlib.Extras
import XMonad.Core
import qualified XMonad.Config as Default
-import XMonad.StackSet (new, floating, member)
+import XMonad.StackSet (new, member)
import qualified XMonad.StackSet as W
import XMonad.Operations
@@ -277,8 +277,7 @@ handle e@(ConfigureRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
bw <- asks (borderWidth . config)
- if M.member w (floating ws)
- || not (member w ws)
+ if not (member w ws)
then do io $ configureWindow dpy w (ev_value_mask e) $ WindowChanges
{ wc_x = ev_x e
, wc_y = ev_y e
@@ -287,7 +286,6 @@ handle e@(ConfigureRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
, wc_border_width = fromIntegral bw
, wc_sibling = ev_above e
, wc_stack_mode = ev_detail e }
- when (member w ws) (float w)
else io $ allocaXEvent $ \ev -> do
setEventType ev configureNotify
setConfigureEvent ev w w
diff --git a/XMonad/ManageHook.hs b/XMonad/ManageHook.hs
index 856c742..64f9fe6 100644
--- a/XMonad/ManageHook.hs
+++ b/XMonad/ManageHook.hs
@@ -27,7 +27,7 @@ import Control.Monad.Reader
import Data.Maybe
import Data.Monoid
import qualified XMonad.StackSet as W
-import XMonad.Operations (floatLocation, reveal)
+import XMonad.Operations (reveal)
-- | Lift an 'X' action to a 'Query'.
liftX :: X a -> Query a
@@ -106,10 +106,6 @@ getStringProperty d w p = do
doF :: (s -> s) -> Query (Endo s)
doF = return . Endo
--- | Move the window to the floating layer.
-doFloat :: ManageHook
-doFloat = ask >>= \w -> doF . W.float w . snd =<< liftX (floatLocation w)
-
-- | Map the window and remove it from the 'WindowSet'.
doIgnore :: ManageHook
doIgnore = ask >>= \w -> liftX (reveal w) >> doF (W.delete w)
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index c005335..c82cb2f 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -49,25 +49,10 @@ import Graphics.X11.Xlib.Extras
-- border set, and its event mask set.
--
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
- -- ensure that float windows don't go over the edge of the screen
- 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.screenWorkspace $ W.current ws
-
+manage w = whenX (not <$> isClient w) $ do
mh <- asks (manageHook . config)
g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
- windows (g . f)
+ windows (g . W.insertUp w)
-- | unmanage. A window no longer exists, remove it from the window
-- list, on whatever workspace it is.
@@ -127,7 +112,6 @@ windows f = do
this = W.view n ws
n = W.tag wsp
tiled = (W.stack . W.screenWorkspace . W.current $ this)
- >>= W.filter (`M.notMember` W.floating ws)
>>= W.filter (`notElem` vis)
viewrect = screenRect $ W.screenDetail w
@@ -137,15 +121,9 @@ windows f = do
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)
+ io $ restackWindows d (map fst rs)
-- return the visible windows for this workspace:
- return vs
+ return rs
let visible = map fst rects
@@ -470,7 +448,7 @@ pointWithin x y r = x >= rect_x r &&
y < rect_y r + fromIntegral (rect_height r)
-- | Make a tiled window floating, using its suggested rectangle
-float :: Window -> X ()
+{-float :: Window -> X ()
float w = do
(sc, rr) <- floatLocation w
windows $ \ws -> W.float w rr . fromMaybe ws $ do
@@ -478,7 +456,7 @@ float w = do
guard $ i `elem` concatMap (map W.tag . W.screenWorkspaces) (W.screens ws)
f <- W.peek ws
sw <- W.lookupWorkspace sc ws
- return (W.focusWindow f . W.shiftWin sw w $ ws)
+ return (W.focusWindow f . W.shiftWin sw w $ ws)-}
-- ---------------------------------------------------------------------
-- Mouse handling
@@ -504,7 +482,7 @@ mouseDrag f done = do
return z
-- | XXX comment me
-mouseMoveWindow :: Window -> X ()
+{-mouseMoveWindow :: Window -> X ()
mouseMoveWindow w = whenX (isClient w) $ withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
@@ -526,7 +504,7 @@ mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
io $ resizeWindow d w `uncurry`
applySizeHintsContents sh (ex - fromIntegral (wa_x wa),
ey - fromIntegral (wa_y wa)))
- (float w)
+ (float w)-}
-- ---------------------------------------------------------------------
-- | Support for window size hints
diff --git a/XMonad/StackSet.hs b/XMonad/StackSet.hs
index da87ccf..dd91c15 100644
--- a/XMonad/StackSet.hs
+++ b/XMonad/StackSet.hs
@@ -39,10 +39,10 @@ module XMonad.StackSet (
tagMember, renameTag, member, findTag, mapWorkspace, mapLayout,
-- * Modifying the stackset
-- $modifyStackset
- insertUp, delete, delete', filter,
+ insertUp, delete, filter,
-- * Setting the master window
-- $settingMW
- swapUp, swapDown, swapMaster, shiftMaster, modify, modify', float, sink, -- needed by users
+ swapUp, swapDown, swapMaster, shiftMaster, modify, modify', -- needed by users
-- * Composite operations
-- $composite
shift, shiftWin,
@@ -55,7 +55,6 @@ import Prelude hiding (filter)
import Data.Function (on)
import Data.Maybe (listToMaybe,isJust,fromMaybe)
import qualified Data.List as L (deleteBy,find,splitAt,filter,nub)
-import qualified Data.Map as M (Map,insert,delete,empty)
-- $intro
--
@@ -134,7 +133,6 @@ import qualified Data.Map as M (Map,insert,delete,empty)
data StackSet i l a sid sd =
StackSet { current :: !(Screen i l a sid sd) -- ^ currently focused workspace
, visible :: [Screen i l a sid sd] -- ^ non-focused workspaces, visible in xinerama
- , floating :: M.Map a RationalRect -- ^ floating windows
} deriving (Show, Read, Eq)
-- | Visible workspaces, and their Xinerama screens.
@@ -195,7 +193,7 @@ abort x = error $ "xmonad: StackSet: " ++ x
--
new :: (Integral s) => l -> [i] -> [sd] -> StackSet i l a s sd
new l wids m | not (null wids) && length m <= length wids && not (null m)
- = StackSet cur visi M.empty
+ = StackSet cur visi
where (seen,_) = L.splitAt (length m) $ map (\i -> Workspace i l Nothing) wids
(cur:visi) = [ Screen i [] s sd | (i, s, sd) <- zip3 seen [0..] m ]
-- now zip up visibles with their screen id
@@ -415,7 +413,7 @@ mapWorkspace f s = s { current = updScr (current s)
-- | Map a function on all the layouts in the 'StackSet'.
mapLayout :: (l -> l') -> StackSet i l a s sd -> StackSet i l' a s sd
-mapLayout f (StackSet v vs m) = StackSet (fScreen v) (map fScreen vs) m
+mapLayout f (StackSet v vs) = StackSet (fScreen v) (map fScreen vs)
where
fScreen (Screen ws hd s sd) = Screen (fWorkspace ws) (map fWorkspace hd) s sd
fWorkspace (Workspace t l s) = Workspace t (f l) s
@@ -475,25 +473,22 @@ insertUp a s = if member a s then s else insert
--
-- * otherwise, delete doesn't affect the master.
--
-delete :: (Ord a, Eq s) => a -> StackSet i l a s sd -> StackSet i l a s sd
-delete w = sink w . delete' w
-
-- | Only temporarily remove the window from the stack, thereby not destroying special
-- information saved in the 'Stackset'
-delete' :: (Eq a, Eq s) => a -> StackSet i l a s sd -> StackSet i l a s sd
-delete' w s = mapWorkspace removeFromWorkspace s
+delete :: (Eq a, Eq s) => a -> StackSet i l a s sd -> StackSet i l a s sd
+delete w s = mapWorkspace removeFromWorkspace s
where removeFromWorkspace ws = ws { stack = stack ws >>= filter (/=w) }
------------------------------------------------------------------------
-- | Given a window, and its preferred rectangle, set it as floating
-- A floating window should already be managed by the 'StackSet'.
-float :: Ord a => a -> RationalRect -> StackSet i l a s sd -> StackSet i l a s sd
-float w r s = s { floating = M.insert w r (floating s) }
+--float :: Ord a => a -> RationalRect -> StackSet i l a s sd -> StackSet i l a s sd
+--float w r s = s { floating = M.insert w r (floating s) }
-- | Clear the floating status of a window
-sink :: Ord a => a -> StackSet i l a s sd -> StackSet i l a s sd
-sink w s = s { floating = M.delete w (floating s) }
+--sink :: Ord a => a -> StackSet i l a s sd -> StackSet i l a s sd
+--sink w s = s { floating = M.delete w (floating s) }
------------------------------------------------------------------------
-- $settingMW
@@ -546,7 +541,7 @@ shiftWin :: (Ord a, Eq a, Eq s, Eq i) => i -> a -> StackSet i l a s sd -> StackS
shiftWin n w s = case findTag w s of
Just from | n `tagMember` s && n /= from -> go from s
_ -> s
- where go from = onWorkspace n (insertUp w) . onWorkspace from (delete' w)
+ where go from = onWorkspace n (insertUp w) . onWorkspace from (delete w)
onWorkspace :: (Eq i, Eq s) => i -> (StackSet i l a s sd -> StackSet i l a s sd)
-> (StackSet i l a s sd -> StackSet i l a s sd)