aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/BoringWindows.hs
blob: e9c32e04f55c81f65dd368d20fc8952b8dfc101e (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
{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, DeriveDataTypeable #-}
{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.BoringWindows
-- Copyright   :  (c) 2008  David Roundy <droundy@darcs.net>
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Adam Vogt <vogt.adam@gmail.com>
-- Stability   :  unstable
-- Portability :  unportable
--
-- BoringWindows is an extension to allow windows to be marked boring
--
-----------------------------------------------------------------------------

module XMonad.Layout.BoringWindows (
                                   -- * Usage
                                   -- $usage
                                   boringWindows, boringAuto,
                                   markBoring, clearBoring,
                                   focusUp, focusDown, focusMaster,

                                   UpdateBoring(UpdateBoring),
                                   BoringMessage(Replace,Merge),
                                   BoringWindows()
                                  ) where

import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
                                    LayoutModifier(handleMessOrMaybeModifyIt, redoLayout))
import XMonad(Typeable, LayoutClass, Message, X, fromMessage,
              sendMessage, windows, withFocused, Window)
import Control.Applicative((<$>))
import Data.List((\\), union)
import Data.Maybe(fromMaybe, listToMaybe, maybeToList)
import qualified Data.Map as M
import qualified XMonad.StackSet as W

-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.BoringWindows
--
-- Then edit your @layoutHook@ by adding the layout modifier:
--
-- > myLayout = boringWindows (Full ||| etc..)
-- > main = xmonad defaultConfig { layoutHook = myLayout }
--
-- Then to your keybindings, add:
--
-- > , ((modm, xK_j), focusUp)
-- > , ((modm, xK_k), focusDown)
-- > , ((modm, xK_m), focusMaster)
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"


data BoringMessage = FocusUp | FocusDown | FocusMaster | IsBoring Window | ClearBoring
                     | Replace String [Window]
                     | Merge String [Window]
                     deriving ( Read, Show, Typeable )

instance Message BoringMessage

-- | UpdateBoring is sent before attempting to view another boring window, so
-- that layouts have a chance to mark boring windows.
data UpdateBoring = UpdateBoring
    deriving (Typeable)
instance Message UpdateBoring

markBoring, clearBoring, focusUp, focusDown, focusMaster :: X ()
markBoring = withFocused (sendMessage . IsBoring)
clearBoring = sendMessage ClearBoring
focusUp = sendMessage UpdateBoring >> sendMessage FocusUp
focusDown = sendMessage UpdateBoring >> sendMessage FocusDown
focusMaster = sendMessage UpdateBoring >> sendMessage FocusMaster

data BoringWindows a = BoringWindows
    { namedBoring :: M.Map String [a] -- ^ store borings with a specific source
    , chosenBoring :: [a]             -- ^ user-chosen borings
    , hiddenBoring :: Maybe [a]       -- ^ maybe mark hidden windows
    } deriving (Show,Read,Typeable)

boringWindows :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a
boringWindows = ModifiedLayout (BoringWindows M.empty [] Nothing)

-- | Mark windows that are not given rectangles as boring
boringAuto :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a
boringAuto = ModifiedLayout (BoringWindows M.empty [] (Just []))

instance LayoutModifier BoringWindows Window where
    redoLayout (b@BoringWindows { hiddenBoring = bs }) _r mst arrs = do
        let bs' = W.integrate' mst \\ map fst arrs
        return (arrs, Just $ b { hiddenBoring = const bs' <$> bs } )

    handleMessOrMaybeModifyIt bst@(BoringWindows nbs cbs lbs) m
        | Just (Replace k ws) <- fromMessage m
        , maybe True (ws/=) (M.lookup k nbs) =
            let nnb = if null ws then M.delete k nbs
                          else M.insert k ws nbs
            in rjl bst { namedBoring = nnb }
        | Just (Merge k ws) <- fromMessage m
        , maybe True (not . null . (ws \\)) (M.lookup k nbs) =
            rjl bst { namedBoring = M.insertWith union k ws nbs }
        | Just (IsBoring w) <- fromMessage m , w `notElem` cbs =
            rjl bst { chosenBoring = w:cbs }
        | Just ClearBoring <- fromMessage m, not (null cbs) =
            rjl bst { namedBoring = M.empty, chosenBoring = []}
        | Just FocusUp <- fromMessage m =
                            do windows $ W.modify' $ skipBoring W.focusUp'
                               return Nothing
        | Just FocusDown <- fromMessage m =
                            do windows $ W.modify' $ skipBoring W.focusDown'
                               return Nothing
        | Just FocusMaster <- fromMessage m =
                            do windows $ W.modify'
                                            $ skipBoring W.focusDown' -- wiggle focus to make sure
                                            . skipBoring W.focusUp'   -- no boring window gets the focus
                                            . focusMaster'
                               return Nothing
        where skipBoring f st = fromMaybe st $ listToMaybe
                                $ filter ((`notElem` W.focus st:bs) . W.focus)
                                $ take (length $ W.integrate st)
                                $ iterate f st
              bs = concat $ cbs:maybeToList lbs ++ M.elems nbs
              rjl = return . Just . Left
    handleMessOrMaybeModifyIt _ _ = return Nothing

-- | Variant of 'focusMaster' that works on a
-- 'Stack' rather than an entire 'StackSet'.
focusMaster' :: W.Stack a -> W.Stack a
focusMaster' c@(W.Stack _ [] _) = c
focusMaster' (W.Stack t ls rs) = W.Stack x [] (xs ++ t : rs) where (x:xs) = reverse ls