aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/LayoutHints.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/LayoutHints.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/LayoutHints.hs')
-rw-r--r--XMonad/Layout/LayoutHints.hs16
1 files changed, 8 insertions, 8 deletions
diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index 91a067f..29a7d3d 100644
--- a/XMonad/Layout/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -26,10 +26,10 @@ import XMonad(LayoutClass(runLayout), mkAdjust, Window,
Dimension, Position, Rectangle(Rectangle),D)
import qualified XMonad.StackSet as W
-import XMonad.Hooks.ManageDocks(Direction(..))
import XMonad.Layout.Decoration(isInStack)
import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
LayoutModifier(modifyLayout, redoLayout, modifierDescription))
+import XMonad.Util.Types(Direction2D(..))
import Control.Applicative((<$>))
import Control.Arrow(Arrow((***), first, second))
import Control.Monad(Monad(return), mapM, join)
@@ -151,7 +151,7 @@ applyHints s root (((w,lrect@(Rectangle a b c d)),adj):xs) =
next = applyHints s root $ mapSnd growOther' xs
in (w,redr):next
-growOther :: (Position, Position) -> Rectangle -> Set Direction -> Rectangle -> Rectangle
+growOther :: (Position, Position) -> Rectangle -> Set Direction2D -> Rectangle -> Rectangle
growOther ds lrect fds r
| dirs <- flipDir <$> Set.toList (Set.intersection adj fds)
, not $ any (uncurry opposite) $ cross dirs =
@@ -161,20 +161,20 @@ growOther ds lrect fds r
adj = adjacent lrect r
cross xs = [ (a,b) | a <- xs, b <- xs ]
- flipDir :: Direction -> Direction
+ flipDir :: Direction2D -> Direction2D
flipDir d = case d of { L -> R; U -> D; R -> L; D -> U }
- opposite :: Direction -> Direction -> Bool
+ opposite :: Direction2D -> Direction2D -> Bool
opposite x y = flipDir x == y
-- | Leave the opposite edges where they were
-grow :: Direction -> (Position,Position) -> Rectangle -> Rectangle
+grow :: Direction2D -> (Position,Position) -> Rectangle -> Rectangle
grow L (px,_ ) (Rectangle x y w h) = Rectangle (x-px) y (w+fromIntegral px) h
grow U (_ ,py) (Rectangle x y w h) = Rectangle x (y-py) w (h+fromIntegral py)
grow R (px,_ ) (Rectangle x y w h) = Rectangle x y (w+fromIntegral px) h
grow D (_ ,py) (Rectangle x y w h) = Rectangle x y w (h+fromIntegral py)
-comparingEdges :: ([Position] -> [Position] -> Bool) -> Rectangle -> Rectangle -> Set Direction
+comparingEdges :: ([Position] -> [Position] -> Bool) -> Rectangle -> Rectangle -> Set Direction2D
comparingEdges surrounds r1 r2 = Set.fromList $ map fst $ filter snd [ (\k -> (dir,k)) $
any and [[dir `elem` [R,L], allEq [a,c,w,y], [b,d] `surrounds` [x,z]]
,[dir `elem` [U,D], allEq [b,d,x,z], [a,c] `surrounds` [w,y]]]
@@ -190,7 +190,7 @@ comparingEdges surrounds r1 r2 = Set.fromList $ map fst $ filter snd [ (\k -> (d
-- first is shrunk, assuming that the root window is fully covered:
-- one direction for a common edge
-- two directions for a common corner
-adjacent :: Rectangle -> Rectangle -> Set Direction
+adjacent :: Rectangle -> Rectangle -> Set Direction2D
adjacent = comparingEdges (all . onClosedInterval)
-- | True whenever two edges touch. not (Set.null $ adjacent x y) ==> touching x y
@@ -219,7 +219,7 @@ centerPlacement = centerPlacement' clamp
1 -> 1
_ -> 0
-freeDirs :: Rectangle -> Rectangle -> Set Direction
+freeDirs :: Rectangle -> Rectangle -> Set Direction2D
freeDirs root = Set.fromList . uncurry (++) . (lr *** ud)
. centerPlacement' signum root
where