diff options
author | trupill <trupill@gmail.com> | 2010-03-31 11:38:08 +0200 |
---|---|---|
committer | trupill <trupill@gmail.com> | 2010-03-31 11:38:08 +0200 |
commit | e2e0e1b5de04531e0e85387499fe78f4ee2fdecf (patch) | |
tree | 69c780569b5702c53d9d9c5398edbce4c3249060 /XMonad/Layout | |
parent | 9f0c5a948f2214bf5bc38aa032b136eaeca8af0c (diff) | |
download | XMonadContrib-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 '')
-rw-r--r-- | XMonad/Layout/Decoration.hs | 33 | ||||
-rw-r--r-- | XMonad/Layout/ImageButtonDecoration.hs | 182 | ||||
-rw-r--r-- | XMonad/Layout/WindowSwitcherDecoration.hs | 36 |
3 files changed, 236 insertions, 15 deletions
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs index 07b15dc..27a4008 100644 --- a/XMonad/Layout/Decoration.hs +++ b/XMonad/Layout/Decoration.hs @@ -43,6 +43,7 @@ import XMonad.Util.NamedWindows (getName) import XMonad.Util.Invisible import XMonad.Util.XUtils import XMonad.Util.Font +import XMonad.Util.Image -- $usage -- This module is intended for layout developers, who want to decorate @@ -66,19 +67,20 @@ decoration s t ds = ModifiedLayout (Decoration (I Nothing) s t ds) -- -- For a collection of 'Theme's see "XMonad.Util.Themes" data Theme = - Theme { activeColor :: String -- ^ Color of the active window - , inactiveColor :: String -- ^ Color of the inactive window - , urgentColor :: String -- ^ Color of the urgent window - , activeBorderColor :: String -- ^ Color of the border of the active window - , inactiveBorderColor :: String -- ^ Color of the border of the inactive window - , urgentBorderColor :: String -- ^ Color of the border of the urgent window - , activeTextColor :: String -- ^ Color of the text of the active window - , inactiveTextColor :: String -- ^ Color of the text of the inactive window - , urgentTextColor :: String -- ^ Color of the text of the urgent window - , fontName :: String -- ^ Font name - , decoWidth :: Dimension -- ^ Maximum width of the decorations (if supported by the 'DecorationStyle') - , decoHeight :: Dimension -- ^ Height of the decorations - , windowTitleAddons :: [(String, Align)] -- ^ Extra text to appear in a window's title bar + Theme { activeColor :: String -- ^ Color of the active window + , inactiveColor :: String -- ^ Color of the inactive window + , urgentColor :: String -- ^ Color of the urgent window + , activeBorderColor :: String -- ^ Color of the border of the active window + , inactiveBorderColor :: String -- ^ Color of the border of the inactive window + , urgentBorderColor :: String -- ^ Color of the border of the urgent window + , activeTextColor :: String -- ^ Color of the text of the active window + , inactiveTextColor :: String -- ^ Color of the text of the inactive window + , urgentTextColor :: String -- ^ Color of the text of the urgent window + , fontName :: String -- ^ Font name + , decoWidth :: Dimension -- ^ Maximum width of the decorations (if supported by the 'DecorationStyle') + , decoHeight :: Dimension -- ^ Height of the decorations + , windowTitleAddons :: [(String, Align)] -- ^ Extra text to appear in a window's title bar + , windowTitleIcons :: [([[Bool]], Placement)] -- ^ Extra icons to appear in a window's title bar } deriving (Show, Read) -- | The default xmonad 'Theme'. @@ -97,6 +99,7 @@ defaultTheme = , decoWidth = 200 , decoHeight = 20 , windowTitleAddons = [] + , windowTitleIcons = [] } -- | A 'Decoration' layout modifier will handle 'SetTheme', a message @@ -393,7 +396,9 @@ updateDeco sh t fs ((w,_),(Just dw,Just (Rectangle _ _ wh ht))) = do return $ size > fromIntegral wh - fromIntegral (ht `div` 2)) (show nw) let als = AlignCenter : map snd (windowTitleAddons t) strs = name : map fst (windowTitleAddons t) - paintAndWrite dw fs wh ht 1 bc borderc tc bc als strs + i_als = map snd (windowTitleIcons t) + icons = map fst (windowTitleIcons t) + paintTextAndIcons dw fs wh ht 1 bc borderc tc bc als strs i_als icons updateDeco _ _ _ (_,(Just w,Nothing)) = hideWindow w updateDeco _ _ _ _ = return () 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 () diff --git a/XMonad/Layout/WindowSwitcherDecoration.hs b/XMonad/Layout/WindowSwitcherDecoration.hs index e38abd4..34f1ab4 100644 --- a/XMonad/Layout/WindowSwitcherDecoration.hs +++ b/XMonad/Layout/WindowSwitcherDecoration.hs @@ -3,6 +3,7 @@ -- | -- Module : XMonad.Layout.WindowSwitcherDecoration -- Copyright : (c) Jan Vornberger 2009 +-- Alejandro Serrano 2010 -- License : BSD3-style (see LICENSE) -- -- Maintainer : jan.vornberger@informatik.uni-oldenburg.de @@ -18,12 +19,14 @@ module XMonad.Layout.WindowSwitcherDecoration ( -- * Usage: -- $usage windowSwitcherDecoration, - windowSwitcherDecorationWithButtons + windowSwitcherDecorationWithButtons, + windowSwitcherDecorationWithImageButtons ) where import XMonad import XMonad.Layout.Decoration import XMonad.Layout.DecorationAddons +import XMonad.Layout.ImageButtonDecoration import XMonad.Layout.DraggingVisualizer import qualified XMonad.StackSet as S import Control.Monad @@ -52,6 +55,16 @@ import Foreign.C.Types(CInt) -- > myL = windowSwitcherDecorationWithButtons shrinkText defaultThemeWithButtons (draggingVisualizer $ layoutHook defaultConfig) -- > main = xmonad defaultConfig { layoutHook = myL } -- +-- Additionaly, there is a version of the decoration that contains image buttons like +-- "XMonad.Layout.ImageButtonDecoration". To use that version, you will need to +-- import "XMonad.Layout.ImageButtonDecoration" as well and modify your @layoutHook@ +-- in the following way: +-- +-- > import XMonad.Layout.ImageButtonDecoration +-- > +-- > myL = windowSwitcherDecorationWithImageButtons shrinkText defaultThemeWithImageButtons (draggingVisualizer $ layoutHook defaultConfig) +-- > main = xmonad defaultConfig { layoutHook = myL } +-- windowSwitcherDecoration :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration WindowSwitcherDecoration s) l a @@ -75,6 +88,27 @@ instance Eq a => DecorationStyle WindowSwitcherDecoration a where unless hasCrossed $ do sendMessage $ DraggingStopped performWindowSwitching mainw +-- Note: the image button code is duplicated from the above +-- because the title bar handle is different + +windowSwitcherDecorationWithImageButtons :: (Eq a, Shrinker s) => s -> Theme + -> l a -> ModifiedLayout (Decoration ImageWindowSwitcherDecoration s) l a +windowSwitcherDecorationWithImageButtons s c = decoration s c $ IWSD True + +data ImageWindowSwitcherDecoration a = IWSD Bool deriving (Show, Read) + +instance Eq a => DecorationStyle ImageWindowSwitcherDecoration a where + describeDeco _ = "ImageWindowSwitcherDeco" + + decorationCatchClicksHook (IWSD withButtons) mainw dFL dFR = if withButtons + then imageTitleBarButtonHandler mainw dFL dFR + else return False + decorationWhileDraggingHook _ ex ey (mainw, r) x y = handleTiledDraggingInProgress ex ey (mainw, r) x y + decorationAfterDraggingHook _ (mainw, _) decoWin = do focus mainw + hasCrossed <- handleScreenCrossing mainw decoWin + unless hasCrossed $ do sendMessage $ DraggingStopped + performWindowSwitching mainw + handleTiledDraggingInProgress :: CInt -> CInt -> (Window, Rectangle) -> Position -> Position -> X () handleTiledDraggingInProgress ex ey (mainw, r) x y = do let rect = Rectangle (x - (fi ex - rect_x r)) |