aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/MagicFocus.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
commit4866f2e367dfcf22a9591231ba40948826a1b438 (patch)
tree7a245caee3f146826b267d773b7eaa80386a818e /XMonad/Layout/MagicFocus.hs
parent47589e1913fb9530481caedb543978a30d4323ea (diff)
downloadXMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.gz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.xz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.zip
Hierarchify
darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz
Diffstat (limited to 'XMonad/Layout/MagicFocus.hs')
-rw-r--r--XMonad/Layout/MagicFocus.hs51
1 files changed, 51 insertions, 0 deletions
diff --git a/XMonad/Layout/MagicFocus.hs b/XMonad/Layout/MagicFocus.hs
new file mode 100644
index 0000000..57e5b7a
--- /dev/null
+++ b/XMonad/Layout/MagicFocus.hs
@@ -0,0 +1,51 @@
+{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.MagicFocus
+-- Copyright : (c) Peter De Wachter <pdewacht@gmail.com>
+-- License : BSD
+--
+-- Maintainer : Peter De Wachter <pdewacht@gmail.com>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Automagically put the focused window in the master area.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.MagicFocus
+ (-- * Usage
+ -- $usage
+ MagicFocus(MagicFocus)
+ ) where
+
+import Graphics.X11.Xlib
+import XMonad
+import XMonad.StackSet
+
+-- $usage
+-- > import XMonad.Layout.MagicFocus
+-- > layouts = [ Layout $ MagicFocus tiled , Layout $ MagicFocus $ Mirror tiled ]
+
+-- %import XMonad.Layout.MagicFocus
+-- %layout , Layout $ MagicFocus tiled
+-- %layout , Layout $ MagicFocus $ Mirror tiled
+
+
+data MagicFocus l a = MagicFocus (l a) deriving ( Show , Read )
+
+instance (LayoutClass l Window) => LayoutClass (MagicFocus l) Window where
+ doLayout = magicFocus
+
+magicFocus :: LayoutClass l Window => MagicFocus l Window -> Rectangle
+ -> Stack Window -> X ([(Window, Rectangle)], Maybe (MagicFocus l Window))
+magicFocus (MagicFocus l) r s =
+ withWindowSet $ \wset -> do
+ (ws,nl) <- doLayout l r (swap s $ peek wset)
+ case nl of
+ Nothing -> return (ws, Nothing)
+ Just l' -> return (ws, Just $ MagicFocus l')
+
+swap :: (Eq a) => Stack a -> Maybe a -> Stack a
+swap (Stack f u d) focused | Just f == focused = Stack f [] (reverse u ++ d)
+ | otherwise = Stack f u d