aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--MetaModule.hs1
-rw-r--r--NoBorders.hs36
2 files changed, 37 insertions, 0 deletions
diff --git a/MetaModule.hs b/MetaModule.hs
index 7ca8c5e..033ece9 100644
--- a/MetaModule.hs
+++ b/MetaModule.hs
@@ -23,6 +23,7 @@ import XMonadContrib.HintedTile ()
import XMonadContrib.LayoutHints ()
import XMonadContrib.Mosaic ()
import XMonadContrib.NamedWindows ()
+import XMonadContrib.NoBorders ()
import XMonadContrib.RotView ()
import XMonadContrib.SimpleDate ()
import XMonadContrib.Spiral ()
diff --git a/NoBorders.hs b/NoBorders.hs
new file mode 100644
index 0000000..1b8ae94
--- /dev/null
+++ b/NoBorders.hs
@@ -0,0 +1,36 @@
+module XMonadContrib.NoBorders ( noBorders, withBorder ) where
+
+-- Make a given layout display without borders. This is useful for
+-- full-screen or tabbed layouts, where you don't really want to waste a
+-- couple of pixels of real estate just to inform yourself that the visible
+-- window has focus.
+
+-- Usage:
+
+-- import XMonadContrib.NoBorders
+
+-- layouts = [ noBorders full, tall, ... ]
+
+import Control.Monad.State ( gets )
+import Graphics.X11.Xlib
+
+import XMonad
+import Operations ( UnDoLayout(UnDoLayout) )
+import qualified StackSet as W
+import {-# SOURCE #-} Config (borderWidth)
+
+noBorders :: Layout -> Layout
+noBorders = withBorder 0
+
+withBorder :: Dimension -> Layout -> Layout
+withBorder bd l = l { doLayout = \r x -> setborders bd >> doLayout l r x
+ , modifyLayout = ml }
+ where ml m | Just UnDoLayout == fromMessage m
+ = do setborders borderWidth
+ fmap (withBorder bd) `fmap` (modifyLayout l) m
+ | otherwise = fmap (withBorder bd) `fmap` (modifyLayout l) m
+
+setborders :: Dimension -> X ()
+setborders bw = withDisplay $ \d ->
+ do ws <- gets (W.integrate . W.stack . W.workspace . W.current . windowset)
+ mapM_ (\w -> io $ setWindowBorderWidth d w bw) ws