aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-11-29 01:24:16 +0100
committerJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-11-29 01:24:16 +0100
commitc7e2085ea1e8ef2f6b282daeda4d846fbf6d6087 (patch)
treedb70f16b90d17957e225bb3f691890bcc0167e4a /XMonad
parent8871f393adde6eed24bfe9dbf3cf902079837f0a (diff)
downloadXMonadContrib-c7e2085ea1e8ef2f6b282daeda4d846fbf6d6087.tar.gz
XMonadContrib-c7e2085ea1e8ef2f6b282daeda4d846fbf6d6087.tar.xz
XMonadContrib-c7e2085ea1e8ef2f6b282daeda4d846fbf6d6087.zip
A decoration with small buttons and a supporting module
Ignore-this: 2d65133bc5b9ad29bad7d06780bdaa4 darcs-hash:20091129002416-594c5-d4c577ef4ed2288a949ae89d06ada5c165c1165c.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Layout/ButtonDecoration.hs55
-rw-r--r--XMonad/Layout/DecorationAddons.hs124
2 files changed, 179 insertions, 0 deletions
diff --git a/XMonad/Layout/ButtonDecoration.hs b/XMonad/Layout/ButtonDecoration.hs
new file mode 100644
index 0000000..43f3045
--- /dev/null
+++ b/XMonad/Layout/ButtonDecoration.hs
@@ -0,0 +1,55 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.ButtonDecoration
+-- Copyright : (c) Jan Vornberger 2009
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : jan.vornberger@informatik.uni-oldenburg.de
+-- Stability : unstable
+-- Portability : not portable
+--
+-- A decoration that includes small buttons on both ends which invoke
+-- various actions when clicked on: Show a window menu (see
+-- "XMonad.Actions.WindowMenu"), minimize, maximize or close the window.
+--
+-- Note: For maximizing and minimizing to actually work, you will need
+-- to integrate "XMonad.Layout.Maximize" and "XMonad.Layout.Minimize" into your
+-- setup. See the documentation of those modules for more information.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.ButtonDecoration
+ ( -- * Usage:
+ -- $usage
+ buttonDeco
+ ) where
+
+import XMonad
+import XMonad.Layout.Decoration
+import XMonad.Layout.DecorationAddons
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.DecorationAddons
+-- > import XMonad.Layout.ButtonDecoration
+--
+-- Then edit your @layoutHook@ by adding the ButtonDecoration to
+-- your layout:
+--
+-- > myL = buttonDeco shrinkText defaultThemeWithButtons (layoutHook defaultConfig)
+-- > main = xmonad defaultConfig { layoutHook = myL }
+--
+
+buttonDeco :: (Eq a, Shrinker s) => s -> Theme
+ -> l a -> ModifiedLayout (Decoration ButtonDecoration s) l a
+buttonDeco s c = decoration s c $ NFD True
+
+data ButtonDecoration a = NFD Bool deriving (Show, Read)
+
+instance Eq a => DecorationStyle ButtonDecoration a where
+ describeDeco _ = "ButtonDeco"
+ decorationCatchClicksHook _ mainw dFL dFR = titleBarButtonHandler mainw dFL dFR
+ decorationAfterDraggingHook _ (mainw, _) decoWin = focus mainw >> handleScreenCrossing mainw decoWin >> return ()
diff --git a/XMonad/Layout/DecorationAddons.hs b/XMonad/Layout/DecorationAddons.hs
new file mode 100644
index 0000000..28b8eb9
--- /dev/null
+++ b/XMonad/Layout/DecorationAddons.hs
@@ -0,0 +1,124 @@
+----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.DecorationAddons
+-- Copyright : (c) Jan Vornberger 2009
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : jan.vornberger@informatik.uni-oldenburg.de
+-- Stability : unstable
+-- Portability : not portable
+--
+-- Various stuff that can be added to the decoration. Most of it
+-- is intended to be used by other modules. See
+-- "XMonad.Layout.ButtonDecoration" for a module that makes use of this.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.DecorationAddons (
+ titleBarButtonHandler
+ ,defaultThemeWithButtons
+ ,handleScreenCrossing
+ ) where
+
+import XMonad
+import qualified XMonad.StackSet as W
+import XMonad.Layout.Decoration
+import XMonad.Actions.WindowMenu
+import XMonad.Layout.Minimize
+import XMonad.Layout.Maximize
+import XMonad.Hooks.ManageDocks
+import XMonad.Util.Font
+import XMonad.Util.PositionStore
+import XMonad.Util.XUtils (fi)
+
+import Control.Applicative((<$>))
+import Data.Maybe
+import qualified Data.Set as S
+
+minimizeButtonOffset :: Int
+minimizeButtonOffset = 48
+
+maximizeButtonOffset :: Int
+maximizeButtonOffset = 25
+
+closeButtonOffset :: Int
+closeButtonOffset = 10
+
+buttonSize :: Int
+buttonSize = 10
+
+-- | A function intended to be plugged into the 'decorationCatchClicksHook' of a decoration.
+-- It will intercept clicks on the buttons of the decoration and invoke the associated action.
+-- To actually see the buttons, you will need to use a theme that includes them.
+-- See 'defaultThemeWithButtons' below.
+titleBarButtonHandler :: Window -> Int -> Int -> X Bool
+titleBarButtonHandler mainw distFromLeft distFromRight = do
+ let action = if (fi distFromLeft <= 3 * buttonSize)
+ then focus mainw >> windowMenu >> return True
+ else if (fi distFromRight >= closeButtonOffset &&
+ fi distFromRight <= closeButtonOffset + buttonSize)
+ then focus mainw >> kill >> return True
+ else if (fi distFromRight >= maximizeButtonOffset &&
+ fi distFromRight <= maximizeButtonOffset + (2 * buttonSize))
+ then focus mainw >> sendMessage (maximizeRestore mainw) >> return True
+ else if (fi distFromRight >= minimizeButtonOffset &&
+ fi distFromRight <= minimizeButtonOffset + buttonSize)
+ then focus mainw >> sendMessage (MinimizeWin mainw) >> return True
+ else return False
+ action
+
+-- | Intended to be used together with 'titleBarButtonHandler'. See above.
+defaultThemeWithButtons :: Theme
+defaultThemeWithButtons = defaultTheme {
+ windowTitleAddons = [ (" (M)", AlignLeft)
+ , ("_" , AlignRightOffset minimizeButtonOffset)
+ , ("[]" , AlignRightOffset maximizeButtonOffset)
+ , ("X" , AlignRightOffset closeButtonOffset)
+ ]
+ }
+
+-- | A function intended to be plugged into the 'decorationAfterDraggingHook' of a decoration.
+-- It will check if the window has been dragged onto another screen and shift it there.
+-- The PositionStore is also updated accordingly, as this is designed to be used together
+-- with "XMonad.Layout.PositionStoreFloat".
+handleScreenCrossing :: Window -> Window -> X Bool
+handleScreenCrossing w decoWin = withDisplay $ \d -> do
+ root <- asks theRoot
+ (_, _, _, px, py, _, _, _) <- io $ queryPointer d root
+ ws <- gets windowset
+ sc <- fromMaybe (W.current ws) <$> pointScreen (fi px) (fi py)
+ maybeWksp <- screenWorkspace $ W.screen sc
+ let targetWksp = maybeWksp >>= \wksp ->
+ W.findTag w ws >>= \currentWksp ->
+ if (currentWksp /= wksp)
+ then Just wksp
+ else Nothing
+ case targetWksp of
+ Just wksp -> do
+ -- find out window under cursor on target workspace
+ -- apparently we have to switch to the workspace first
+ -- to make this work, which unforunately introduces some flicker
+ windows $ \ws' -> W.view wksp ws'
+ (_, _, selWin, _, _, _, _, _) <- io $ queryPointer d root
+
+ -- adjust PositionStore
+ let oldScreenRect = screenRect . W.screenDetail $ W.current ws
+ newScreenRect = screenRect . W.screenDetail $ sc
+ {-- somewhat ugly hack to get proper ScreenRect,
+ creates unwanted inter-dependencies
+ TODO: get ScreenRects in a proper way --}
+ oldScreenRect' <- fmap ($ oldScreenRect) (calcGap $ S.fromList [minBound .. maxBound])
+ newScreenRect' <- fmap ($ newScreenRect) (calcGap $ S.fromList [minBound .. maxBound])
+ wa <- io $ getWindowAttributes d decoWin
+ modifyPosStore (\ps ->
+ posStoreMove ps w (fi $ wa_x wa) (fi $ wa_y wa)
+ oldScreenRect' newScreenRect')
+
+ -- set focus correctly so the window will be inserted
+ -- at the correct position on the target workspace
+ -- and then shift the window
+ windows $ \ws' -> W.shiftWin wksp w . W.focusWindow selWin $ ws'
+
+ -- return True to signal that screen crossing has taken place
+ return True
+ Nothing -> return False