aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/ResizeScreen.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-01-27 02:07:55 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-01-27 02:07:55 +0100
commitd53b46fdd2de0f9ea1e884a550ca0e80dc3ddba5 (patch)
treec2a898ce150c8bd9c48370be4db78bd38f22e173 /XMonad/Layout/ResizeScreen.hs
parent393f14979694137423eacffcc7ef3bc14fa69ed6 (diff)
downloadXMonadContrib-d53b46fdd2de0f9ea1e884a550ca0e80dc3ddba5.tar.gz
XMonadContrib-d53b46fdd2de0f9ea1e884a550ca0e80dc3ddba5.tar.xz
XMonadContrib-d53b46fdd2de0f9ea1e884a550ca0e80dc3ddba5.zip
Add ResizeScreen, a layout modifier for modifing the screen geometry
darcs-hash:20080127010755-32816-5e5262602de3f23f7da24d9d854fb0d6a4c22e8e.gz
Diffstat (limited to 'XMonad/Layout/ResizeScreen.hs')
-rw-r--r--XMonad/Layout/ResizeScreen.hs81
1 files changed, 81 insertions, 0 deletions
diff --git a/XMonad/Layout/ResizeScreen.hs b/XMonad/Layout/ResizeScreen.hs
new file mode 100644
index 0000000..4b56e96
--- /dev/null
+++ b/XMonad/Layout/ResizeScreen.hs
@@ -0,0 +1,81 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.ResizeScreen
+-- Copyright : (c) 2007 Andrea Rossato
+-- License : BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer : andrea.rossato@unibz.it
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A layout transformer to have a layout respect a given screen
+-- geometry
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.ResizeScreen
+ ( -- * Usage:
+ -- $usage
+ resizeHorizontal
+ , resizeVertical
+ , withNewRectangle
+ , ResizeScreen (..)
+ ) where
+
+import Control.Arrow (second)
+import Control.Applicative ((<$>))
+
+import XMonad
+import XMonad.Util.XUtils (fi)
+
+-- $usage
+-- You can use this module by importing it into your
+-- @~\/.xmonad\/xmonad.hs@ file:
+--
+-- > import XMonad.Layout.ResizeScreen
+--
+-- and modifying your layoutHook as follows (for example):
+--
+-- > layoutHook = resizeHorizontal 40 Full
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+
+resizeHorizontal :: Int -> l a -> ResizeScreen l a
+resizeHorizontal = ResizeScreen H
+
+resizeVertical :: Int -> l a -> ResizeScreen l a
+resizeVertical = ResizeScreen V
+
+withNewRectangle :: Rectangle -> l a -> ResizeScreen l a
+withNewRectangle = WithNewScreen
+
+data ResizeScreen l a = ResizeScreen ResizeMode Int (l a)
+ | WithNewScreen Rectangle (l a)
+ deriving (Read, Show)
+data ResizeMode = H | V deriving (Read, Show)
+
+instance (LayoutClass l a) => LayoutClass (ResizeScreen l) a where
+ doLayout m (Rectangle x y w h ) s
+ | ResizeScreen H i l <- m = resize (ResizeScreen V i) l (Rectangle (x + fi i) y (w - fi i) h)
+ | ResizeScreen V i l <- m = resize (ResizeScreen H i) l (Rectangle x (y + fi i) w (h - fi i))
+ | WithNewScreen r l <- m = resize (WithNewScreen r) l r
+ | otherwise = return ([],Nothing)
+ where resize t l' nr = second (fmap t) <$> doLayout l' nr s
+
+ handleMessage rs m
+ | ResizeScreen t i l <- rs = go (ResizeScreen t i) l
+ | WithNewScreen r l <- rs = go (WithNewScreen r) l
+ | otherwise = return Nothing
+ where go tp lay = do ml' <- handleMessage lay m
+ return (tp `fmap` ml')
+
+ emptyLayout rs re
+ | ResizeScreen t i l <- rs = go (ResizeScreen t i) l
+ | WithNewScreen r l <- rs = go (WithNewScreen r) l
+ | otherwise = return ([],Nothing)
+ where go tp lay = do (wrs,ml) <- emptyLayout lay re
+ return (wrs, tp `fmap` ml)
+
+ description _ = []