aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/WindowNavigation.hs
diff options
context:
space:
mode:
authorDaniel Schoepe <daniel.schoepe@gmail.com>2009-09-19 21:17:17 +0200
committerDaniel Schoepe <daniel.schoepe@gmail.com>2009-09-19 21:17:17 +0200
commitc1a6ed7be8b090cea63a70fa86ee614d011d0f63 (patch)
tree2611d41215616daba97a239330d85a00123f44e6 /XMonad/Layout/WindowNavigation.hs
parent3bd3fd1d4bd1af1ffe306307a80387c82d304664 (diff)
downloadXMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.tar.gz
XMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.tar.xz
XMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.zip
Factor out direction types and put them in X.U.Types
Ignore-this: b2255ec2754fcdf797b1ce2c082642ba This patch factors out commonly used direction types like data Direction darcs-hash:20090919191717-7f603-09c283e51a0b886d260008676d71e3daf31f4394.gz
Diffstat (limited to 'XMonad/Layout/WindowNavigation.hs')
-rw-r--r--XMonad/Layout/WindowNavigation.hs17
1 files changed, 8 insertions, 9 deletions
diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index 0dd6d43..34660be 100644
--- a/XMonad/Layout/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -18,7 +18,7 @@ module XMonad.Layout.WindowNavigation (
-- * Usage
-- $usage
windowNavigation, configurableNavigation,
- Navigate(..), Direction(..),
+ Navigate(..), Direction2D(..),
MoveWindowToWindow(..),
navigateColor, navigateBrightness,
noNavigateBorders, defaultWNConfig
@@ -29,10 +29,9 @@ import XMonad hiding (Point)
import qualified XMonad.StackSet as W
import XMonad.Layout.LayoutModifier
import XMonad.Util.Invisible
+import XMonad.Util.Types (Direction2D(..))
import XMonad.Util.XUtils
-import XMonad.Hooks.ManageDocks (Direction(..))
-
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
@@ -67,8 +66,8 @@ import XMonad.Hooks.ManageDocks (Direction(..))
data MoveWindowToWindow a = MoveWindowToWindow a a deriving ( Read, Show, Typeable )
instance Typeable a => Message (MoveWindowToWindow a)
-data Navigate = Go Direction | Swap Direction | Move Direction
- | Apply (Window -> X()) Direction -- ^ Apply action with destination window
+data Navigate = Go Direction2D | Swap Direction2D | Move Direction2D
+ | Apply (Window -> X()) Direction2D -- ^ Apply action with destination window
deriving ( Typeable )
instance Message Navigate
@@ -188,7 +187,7 @@ instance LayoutModifier WindowNavigation Window where
handleMessOrMaybeModifyIt (WindowNavigation conf (I $ Just (NS pt wrs))) (SomeMessage Hide)
handleMessOrMaybeModifyIt _ _ = return Nothing
-navigable :: Direction -> Point -> [(Window, Rectangle)] -> [(Window, Rectangle)]
+navigable :: Direction2D -> Point -> [(Window, Rectangle)] -> [(Window, Rectangle)]
navigable d pt = sortby d . filter (inr d pt . snd)
sc :: Pixel -> Window -> X ()
@@ -197,11 +196,11 @@ sc c win = withDisplay $ \dpy -> io $ setWindowBorder dpy win c
center :: Rectangle -> Point
center (Rectangle x y w h) = P (fromIntegral x + fromIntegral w/2) (fromIntegral y + fromIntegral h/2)
-centerd :: Direction -> Point -> Rectangle -> Point
+centerd :: Direction2D -> Point -> Rectangle -> Point
centerd d (P xx yy) (Rectangle x y w h) | d == U || d == D = P xx (fromIntegral y + fromIntegral h/2)
| otherwise = P (fromIntegral x + fromIntegral w/2) yy
-inr :: Direction -> Point -> Rectangle -> Bool
+inr :: Direction2D -> Point -> Rectangle -> Bool
inr D (P x y) (Rectangle l yr w h) = x >= fromIntegral l && x < fromIntegral l + fromIntegral w &&
y < fromIntegral yr + fromIntegral h
inr U (P x y) (Rectangle l yr w _) = x >= fromIntegral l && x < fromIntegral l + fromIntegral w &&
@@ -215,7 +214,7 @@ inrect :: Point -> Rectangle -> Bool
inrect (P x y) (Rectangle a b w h) = x > fromIntegral a && x < fromIntegral a + fromIntegral w &&
y > fromIntegral b && y < fromIntegral b + fromIntegral h
-sortby :: Direction -> [(a,Rectangle)] -> [(a,Rectangle)]
+sortby :: Direction2D -> [(a,Rectangle)] -> [(a,Rectangle)]
sortby U = sortBy (\(_,Rectangle _ y _ _) (_,Rectangle _ y' _ _) -> compare y' y)
sortby D = sortBy (\(_,Rectangle _ y _ _) (_,Rectangle _ y' _ _) -> compare y y')
sortby R = sortBy (\(_,Rectangle x _ _ _) (_,Rectangle x' _ _ _) -> compare x x')