
New patches:

[Fix float behaviour, add shiftWin.
Karsten Schoelzel <kuser@gmx.de>**20070910090329
 
 First, if float is called with window which is on a hidden workspace,
 then the window will remain on that hidden workspace.
 
 Now the focus should change more as expected:
 float w = (view current) . (shiftWin ws w)
     where
         current is the current screen/workspace
         shiftWin ws w is: - view the workspace w is on
             - set focus on w
             - shift ws
             - set focus back to window it was on that workspace
                 unless w was focused
 
 shiftWin was add to StackSet.hs 
] {
hunk ./Main.hs 32
-import StackSet (new, floating, member, findIndex, workspace, tag, current, visible)
+import StackSet (new, floating, member)
hunk ./Main.hs 229
-    -- TODO temporary workaround for some bugs in float.  Don't call 'float' on
-    -- windows that aren't visible, because it changes the focused screen
-    let vis = any ((== findIndex w ws) . Just . tag . workspace) (current ws : visible ws)
-    if (M.member w (floating ws) && vis)
+    if M.member w (floating ws)
hunk ./Operations.hs 479
---
--- TODO: float changes the set of visible workspaces when we call it for an
--- invisible window -- this should not happen.  See 'temporary workaround' in
--- the handler for ConfigureRequestEvent also.
hunk ./Operations.hs 488
+        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)))
hunk ./Operations.hs 493
-    windows $ maybe id W.focusWindow (W.peek ws) . W.shift sw . W.focusWindow w . W.float w
-        (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)))
+    if maybe False (`elem` (map W.tag . W.hidden $ ws)) (W.findIndex w ws)
+        then windows $ W.float w rr
+        else windows $ maybe id W.focusWindow (W.peek ws) . W.shiftWin sw w . W.float w rr
hunk ./StackSet.hs 35
-        shift
+        shift, shiftWin
hunk ./StackSet.hs 39
-import Data.Maybe   (listToMaybe)
+import Data.Maybe   (listToMaybe,fromJust)
hunk ./StackSet.hs 501
+shiftWin :: (Ord a, Eq a, Eq s, Eq i) => i -> a -> StackSet i a s sd -> StackSet i a s sd
+shiftWin n w s | from == Nothing                     = s
+               | n `tagMember` s && (Just n) /= from = go
+               | otherwise                           = s
+    where go = on n (insertUp w) . on (fromJust from) (delete' w) $ s
+          curtag = tag (workspace (current s))
+          from = findIndex w s
+          on i f = view curtag . f . view i
+
hunk ./tests/Properties.hs 170
+prop_shift_win_I (n :: NonNegative Int) (w :: Char) (x :: T) =
+    n `tagMember` x && w `member` x ==> invariant $ shiftWin (fromIntegral n) w x
+
hunk ./tests/Properties.hs 499
+-- ---------------------------------------------------------------------
+-- shiftWin
+
+-- shiftWin on current window is the same as shift
+prop_shift_win_focus i (x :: T) =
+    i `tagMember` x ==> case peek x of
+                          Nothing -> True
+                          Just w  -> shiftWin i w x == shift i x
+
+-- shiftWin leaves the current screen as it is, if neither i is the tag
+-- of the current workspace nor w on the current workspace
+prop_shift_win_fix_current i w (x :: T) =
+    i `tagMember` x && w `member` x && i /= n && findIndex w x /= Just n 
+        ==> (current $ x) == (current $ shiftWin i w x)
+    where
+        n = tag (workspace $ current x)
+
hunk ./tests/Properties.hs 634
+        ,("shiftWin: invariant" , mytest prop_shift_win_I)
+        ,("shiftWin is shift on focus" , mytest prop_shift_win_focus)
+        ,("shiftWin fix current" , mytest prop_shift_win_fix_current)
}

Context:

[Move lower boundary check into applySizeHints, because all users of applySizeHints
Karsten Schoelzel <kuser@gmx.de>**20070905192125
 do this manually.
] 
[export getAtom from XMonad.
Ivan Tarasov <Ivan.Tarasov@gmail.com>**20070825174156] 
[Use show rather than string hacks
Spencer Janssen <sjanssen@cse.unl.edu>**20070905202816] 
[switch WorkspaceId to String.
David Roundy <droundy@darcs.net>**20070820113658] 
[Alex Tarkovsky's docstring patch updated for conflicts
Spencer Janssen <sjanssen@cse.unl.edu>**20070905193558] 
[tasks done
Don Stewart <dons@cse.unsw.edu.au>**20070905004901] 
[TAG 0.3
Spencer Janssen <sjanssen@cse.unl.edu>**20070904195245] 
Patch bundle hash:
8ecc4bc5fa8a3a50349fcb0f3a17e1433a7f7de6
