aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/ImageButtonDecoration.hs
blob: 23c6cc304d04bcb98a4a555bcf0e81c4f6361818 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
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' = [[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,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1]]

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 >> minimizeWindow 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 ()