aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/ImageButtonDecoration.hs
diff options
context:
space:
mode:
authortrupill <trupill@gmail.com>2010-03-31 11:38:08 +0200
committertrupill <trupill@gmail.com>2010-03-31 11:38:08 +0200
commite2e0e1b5de04531e0e85387499fe78f4ee2fdecf (patch)
tree69c780569b5702c53d9d9c5398edbce4c3249060 /XMonad/Layout/ImageButtonDecoration.hs
parent9f0c5a948f2214bf5bc38aa032b136eaeca8af0c (diff)
downloadXMonadContrib-e2e0e1b5de04531e0e85387499fe78f4ee2fdecf.tar.gz
XMonadContrib-e2e0e1b5de04531e0e85387499fe78f4ee2fdecf.tar.xz
XMonadContrib-e2e0e1b5de04531e0e85387499fe78f4ee2fdecf.zip
image_buttons
Ignore-this: 418dbf488435c7c803695407557eecfb * Added a XMonad.Util.Image module to manipulate simple images and show them into an X drawable * Added the possibility of using image buttons instead of plain text buttons into the title bar * Added a XMonad.Layout.ImageButtonDecoration as an example of how to use the image buttons darcs-hash:20100331093808-a84fe-e6d3ce505f7656eef13f0c0609a8d236d9cd8d25.gz
Diffstat (limited to 'XMonad/Layout/ImageButtonDecoration.hs')
-rw-r--r--XMonad/Layout/ImageButtonDecoration.hs182
1 files changed, 182 insertions, 0 deletions
diff --git a/XMonad/Layout/ImageButtonDecoration.hs b/XMonad/Layout/ImageButtonDecoration.hs
new file mode 100644
index 0000000..5e30044
--- /dev/null
+++ b/XMonad/Layout/ImageButtonDecoration.hs
@@ -0,0 +1,182 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.ImageButtonDecoration
+-- Copyright : (c) Jan Vornberger 2009
+-- Alejandro Serrano 2010
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : trupill@gmail.com
+-- Stability : unstable
+-- Portability : not portable
+--
+-- A decoration that includes small image 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.
+--
+-----------------------------------------------------------------------------
+
+-- This module is mostly derived from "XMonad.Layout.DecorationAddons"
+-- and "XMonad.Layout.ButtonDecoration"
+
+module XMonad.Layout.ImageButtonDecoration
+ ( -- * Usage:
+ -- $usage
+ imageButtonDeco
+ , defaultThemeWithImageButtons
+ , imageTitleBarButtonHandler
+ ) where
+
+import XMonad
+import XMonad.Layout.Decoration
+import XMonad.Layout.DecorationAddons
+import XMonad.Util.Image
+
+import XMonad.Actions.WindowMenu
+import XMonad.Layout.Minimize
+import XMonad.Layout.Maximize
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.ImageButtonDecoration
+--
+-- Then edit your @layoutHook@ by adding the ImageButtonDecoration to
+-- your layout:
+--
+-- > myL = imageButtonDeco shrinkText defaultThemeWithImageButtons (layoutHook defaultConfig)
+-- > main = xmonad defaultConfig { layoutHook = myL }
+--
+
+-- The buttons' dimension and placements
+
+buttonSize :: Int
+buttonSize = 10
+
+menuButtonOffset :: Int
+menuButtonOffset = 4
+
+minimizeButtonOffset :: Int
+minimizeButtonOffset = 32
+
+maximizeButtonOffset :: Int
+maximizeButtonOffset = 18
+
+closeButtonOffset :: Int
+closeButtonOffset = 4
+
+
+-- The images in a 0-1 scale to make
+-- it easier to visualize
+
+convertToBool' :: [Int] -> [Bool]
+convertToBool' = map (\x -> x == 1)
+
+convertToBool :: [[Int]] -> [[Bool]]
+convertToBool = map convertToBool'
+
+menuButton' :: [[Int]]
+menuButton' = [[0,0,0,0,1,1,0,0,0,0],
+ [0,0,0,1,1,1,1,0,0,0],
+ [0,0,1,1,0,0,1,1,0,0],
+ [0,1,1,0,0,0,0,1,1,0],
+ [1,1,0,0,1,1,0,0,1,1],
+ [1,1,0,0,1,1,0,0,1,1],
+ [0,1,1,0,0,0,0,1,1,0],
+ [0,0,1,1,0,0,1,1,0,0],
+ [0,0,0,1,1,1,1,0,0,0],
+ [0,0,0,0,1,1,0,0,0,0]]
+
+menuButton :: [[Bool]]
+menuButton = convertToBool menuButton'
+
+miniButton' :: [[Int]]
+miniButton' = [[0,0,0,0,0,0,0,0,0,0],
+ [0,0,0,0,0,0,0,0,0,0],
+ [0,0,0,0,0,0,0,0,0,0],
+ [0,0,0,0,0,0,0,0,0,0],
+ [0,0,0,0,0,0,0,0,0,0],
+ [0,0,0,0,0,0,0,0,0,0],
+ [0,0,0,0,0,0,0,0,0,0],
+ [0,0,0,0,0,0,0,0,0,0],
+ [1,1,1,1,1,1,1,1,1,1],
+ [1,1,1,1,1,1,1,1,1,1]]
+
+miniButton :: [[Bool]]
+miniButton = convertToBool miniButton'
+
+maxiButton' :: [[Int]]
+maxiButton' = [[1,1,1,1,1,1,1,1,1,1],
+ [1,1,1,1,1,1,1,1,1,1],
+ [1,1,0,0,0,0,0,0,1,1],
+ [1,1,0,0,0,0,0,0,1,1],
+ [1,1,0,0,0,0,0,0,1,1],
+ [1,1,0,0,0,0,0,0,1,1],
+ [1,1,0,0,0,0,0,0,1,1],
+ [1,1,0,0,0,0,0,0,1,1],
+ [1,1,1,1,1,1,1,1,1,1],
+ [1,1,1,1,1,1,1,1,1,1]]
+
+maxiButton :: [[Bool]]
+maxiButton = convertToBool maxiButton'
+
+closeButton' :: [[Int]]
+closeButton' = [[1,1,0,0,0,0,0,0,1,1],
+ [1,1,1,0,0,0,0,1,1,1],
+ [0,1,1,1,0,0,1,1,1,0],
+ [0,0,1,1,1,1,1,1,0,0],
+ [0,0,0,1,1,1,1,0,0,0],
+ [0,0,0,1,1,1,1,0,0,0],
+ [0,0,1,1,1,1,1,1,0,0],
+ [0,1,1,1,0,0,1,1,1,0],
+ [1,1,1,0,0,0,0,1,1,1],
+ [1,1,0,0,0,0,0,0,1,1]]
+
+
+closeButton :: [[Bool]]
+closeButton = convertToBool closeButton'
+
+-- | 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 'defaultThemeWithImageButtons' below.
+imageTitleBarButtonHandler :: Window -> Int -> Int -> X Bool
+imageTitleBarButtonHandler mainw distFromLeft distFromRight = do
+ let action = if (fi distFromLeft >= menuButtonOffset &&
+ fi distFromLeft <= menuButtonOffset + 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 + 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
+
+defaultThemeWithImageButtons :: Theme
+defaultThemeWithImageButtons = defaultTheme {
+ windowTitleIcons = [ (menuButton, CenterLeft 3),
+ (closeButton, CenterRight 3),
+ (maxiButton, CenterRight 18),
+ (miniButton, CenterRight 33) ]
+ }
+
+imageButtonDeco :: (Eq a, Shrinker s) => s -> Theme
+ -> l a -> ModifiedLayout (Decoration ImageButtonDecoration s) l a
+imageButtonDeco s c = decoration s c $ NFD True
+
+data ImageButtonDecoration a = NFD Bool deriving (Show, Read)
+
+instance Eq a => DecorationStyle ImageButtonDecoration a where
+ describeDeco _ = "ImageButtonDeco"
+ decorationCatchClicksHook _ mainw dFL dFR = imageTitleBarButtonHandler mainw dFL dFR
+ decorationAfterDraggingHook _ (mainw, _) decoWin = focus mainw >> handleScreenCrossing mainw decoWin >> return ()