aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/CopyWindow.hs
blob: d49b5dc14e8eb9803bddb46b85999752e4ccc71b (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
{-# LANGUAGE PatternGuards #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Actions.CopyWindow
-- Copyright   :  (c) David Roundy <droundy@darcs.net>, Ivan Veselov <veselov@gmail.com>, Lanny Ripple <lan3ny@gmail.com>
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  ???
-- Stability   :  unstable
-- Portability :  unportable
--
-- Provides a binding to duplicate a window on multiple workspaces,
-- providing dwm-like tagging functionality.
--
-----------------------------------------------------------------------------

module XMonad.Actions.CopyWindow (
                                 -- * Usage
                                 -- $usage
                                 copy, copyToAll, copyWindow, runOrCopy
                                 , killAllOtherCopies, kill1
                                ) where

import Prelude hiding (filter)
import Control.Monad (filterM)
import qualified Data.List as L
import XMonad hiding (modify, workspaces)
import qualified XMonad.StackSet as W

-- $usage
--
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
--
-- > import XMonad.Actions.CopyWindow
--
-- Then add something like this to your keybindings:
--
-- > -- mod-[1..9] @@ Switch to workspace N
-- > -- mod-shift-[1..9] @@ Move client to workspace N
-- > -- mod-control-shift-[1..9] @@ Copy client to workspace N
-- > [((m .|. modMask x, k), windows $ f i)
-- >     | (i, k) <- zip (workspaces x) [xK_1 ..]
-- >     , (f, m) <- [(W.view, 0), (W.shift, shiftMask), (copy, shiftMask .|. controlMask)]]
--
-- To use the above key bindings you need also to import
-- "XMonad.StackSet":
--
-- > import qualified XMonad.StackSet as W
--
-- You may also wish to redefine the binding to kill a window so it only
-- removes it from the current workspace, if it's present elsewhere:
--
-- >  , ((modMask x .|. shiftMask, xK_c     ), kill1) -- @@ Close the focused window
--
-- Instead of copying a window from a workset to a workset maybe you don't
-- want to have to remember where you placed it.  For that consider:
--
-- >  , ((modMask x, xK_b    ), runOrCopy "firefox" (className =? "Firefox")) -- @@ run or copy firefox
--
-- Another possibility which this extension provides is 'making window
-- always visible' (i.e. always on current workspace), similar to corresponding
-- metacity functionality. This behaviour is emulated through copying given
-- window to all the workspaces and then removing it when it's unneeded on
-- all workspaces any more.
--
-- Here is the example of keybindings which provide these actions:
--
-- >  , ((modMask x, xK_v ), windows copyToAll) -- @@ Make focused window always visible
-- >  , ((modMask x .|. shiftMask, xK_v ),  killAllOtherCopies) -- @@ Toggle window state back
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".

-- | copy. Copy the focused window to a new workspace.
copy :: (Eq s, Eq i, Eq a) => i -> W.StackSet i l a s sd -> W.StackSet i l a s sd
copy n s | Just w <- W.peek s = copyWindow w n s
         | otherwise = s

-- | copyToAll. Copy the focused window to all of workspaces.
copyToAll :: (Eq s, Eq i, Eq a) => W.StackSet i l a s sd -> W.StackSet i l a s sd
copyToAll s = foldr copy s $ map W.tag (W.workspaces s)

-- | copyWindow.  Copy a window to a new workspace
copyWindow :: (Eq a, Eq i, Eq s) => a -> i -> W.StackSet i l a s sd -> W.StackSet i l a s sd
copyWindow w n = copy'
    where copy' s = if n `W.tagMember` s
                    then W.view (W.currentTag s) $ insertUp' w $ W.view n s
                    else s
          insertUp' a s = W.modify (Just $ W.Stack a [] [])
                          (\(W.Stack t l r) -> if a `elem` t:l++r
                                             then Just $ W.Stack t l r
                                             else Just $ W.Stack a (L.delete a l) (L.delete a (t:r))) s


-- | runOrCopy .  runOrCopy will run the provided shell command unless it can
--  find a specified window in which case it will copy the window to
--  the current workspace.  Similar to (i.e., stolen from) "XMonad.Actions.WindowGo".
runOrCopy :: String -> Query Bool -> X ()
runOrCopy = copyMaybe . spawn

-- | copyMaybe. Copies "XMonad.Actions.WindowGo" ('raiseMaybe')
--   TODO: Factor out and improve with regard to WindowGo.
copyMaybe :: X () -> Query Bool -> X ()
copyMaybe f thatUserQuery = withWindowSet $ \s -> do
    maybeResult <- filterM (runQuery thatUserQuery) (W.allWindows s)
    case maybeResult of
        []    -> f
        (x:_) -> windows $ copyWindow x (W.currentTag s)


-- | Remove the focused window from this workspace.  If it's present in no
-- other workspace, then kill it instead. If we do kill it, we'll get a
-- delete notify back from X.
--
-- There are two ways to delete a window. Either just kill it, or if it
-- supports the delete protocol, send a delete event (e.g. firefox)
kill1 :: X ()
kill1 = do ss <- gets windowset
           whenJust (W.peek ss) $ \w -> if W.member w $ delete'' w ss
                                      then windows $ delete'' w
                                      else kill
    where delete'' w = W.modify Nothing (W.filter (/= w))

-- | Kill all other copies of focused window (if they're present)
-- 'All other' means here 'copies, which are not on current workspace'
--
-- TODO: Call this function after 'copyToAll'?
killAllOtherCopies :: X ()
killAllOtherCopies = do ss <- gets windowset
                        whenJust (W.peek ss) $ \w -> windows $
                                                   W.view (W.currentTag ss) .
                                                   delFromAllButCurrent w
    where
      delFromAllButCurrent w ss = foldr ($) ss $
                                  map (delWinFromWorkspace w . W.tag) $
                                  W.hidden ss ++ map W.workspace (W.visible ss)
      delWinFromWorkspace w wid = W.modify Nothing (W.filter (/= w)) . W.view wid