From bf67ffe8b42cbc8167f6f680231f82a9b2b9fbec Mon Sep 17 00:00:00 2001 From: Andrea Rossato Date: Fri, 28 Sep 2007 20:59:07 +0200 Subject: WindowNavigation now uses Invisible (plus some vertical alignement) darcs-hash:20070928185907-32816-46314c30342aa7aeae9924bba0d98629824ef833.gz --- WindowNavigation.hs | 37 +++++++++++++++++-------------------- 1 file changed, 17 insertions(+), 20 deletions(-) (limited to 'WindowNavigation.hs') diff --git a/WindowNavigation.hs b/WindowNavigation.hs index ffc8df9..9e44182 100644 --- a/WindowNavigation.hs +++ b/WindowNavigation.hs @@ -27,6 +27,7 @@ import XMonad import qualified StackSet as W import Operations ( focus, initColor ) import XMonadContrib.LayoutModifier +import XMonadContrib.Invisible -- $usage -- You can use this module with the following in your Config.hs file: @@ -56,15 +57,11 @@ data Navigate = Go Direction deriving ( Read, Show, Typeable ) data Direction = U | D | R | L deriving ( Read, Show, Eq ) instance Message Navigate -data InvisibleMaybe a = INothin | IJus a -instance Show (InvisibleMaybe a) where show _ = "" -instance Read (InvisibleMaybe a) where readsPrec _ s = [(INothin, s)] - data NavigationState a = NS Point [(a,Rectangle)] -data WindowNavigation a = WindowNavigation (InvisibleMaybe (NavigationState a)) deriving ( Read, Show ) +data WindowNavigation a = WindowNavigation (Invisible Maybe (NavigationState a)) deriving ( Read, Show ) -windowNavigation = ModifiedLayout (WindowNavigation INothin) +windowNavigation = ModifiedLayout (WindowNavigation (I Nothing)) instance LayoutModifier WindowNavigation Window where redoLayout (WindowNavigation state) rscr s wrs = @@ -77,34 +74,34 @@ instance LayoutModifier WindowNavigation Window where w = W.focus s r = case filter ((==w).fst) wrs of ((_,x):_) -> x [] -> rscr - pt = case state of IJus (NS ptold _) | ptold `inrect` r -> ptold + pt = case state of I (Just (NS ptold _)) | ptold `inrect` r -> ptold _ -> center r wrs' = filter ((/=w) . fst) wrs wnavigable = nub $ map fst $ concatMap (\d -> filter (inr d pt . snd) wrs') [U,D,R,L] wothers = map fst wrs' \\ wnavigable --mapM_ (sc navigableColor) wnavigable --mapM_ (sc otherColor) wothers - return (wrs, Just $ WindowNavigation $ IJus $ NS pt wrs') - modifyModify (WindowNavigation (IJus (NS pt wrs))) m + return (wrs, Just $ WindowNavigation $ I $ Just $ NS pt wrs') + modifyModify (WindowNavigation (I (Just (NS pt wrs)))) m | Just (Go d) <- fromMessage m = case sortby d $ filter (inr d pt . snd) wrs of [] -> return Nothing ((w,r):_) -> do focus w - return $ Just $ WindowNavigation $ IJus $ NS (centerd d pt r) [] + return $ Just $ WindowNavigation $ I $ Just $ NS (centerd d pt r) [] modifyModify _ _ = return Nothing center (Rectangle x y w h) = P (fromIntegral x + fromIntegral w/2) (fromIntegral y + fromIntegral h/2) 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 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 && - y > fromIntegral yr -inr R (P a x) (Rectangle b l _ w) = x >= fromIntegral l && x <= fromIntegral l + fromIntegral w && - a < fromIntegral b -inr L (P a x) (Rectangle b l c w) = x >= fromIntegral l && x <= fromIntegral l + fromIntegral w && - a > fromIntegral b + fromIntegral c -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 +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 && + y > fromIntegral yr +inr R (P a x) (Rectangle b l _ w) = x >= fromIntegral l && x <= fromIntegral l + fromIntegral w && + a < fromIntegral b +inr L (P a x) (Rectangle b l c w) = x >= fromIntegral l && x <= fromIntegral l + fromIntegral w && + a > fromIntegral b + fromIntegral c +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 U = sortBy (\(_,Rectangle _ y _ _) (_,Rectangle _ y' _ _) -> compare y' y) sortby D = sortBy (\(_,Rectangle _ y _ _) (_,Rectangle _ y' _ _) -> compare y y') -- cgit v1.2.3