aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Prompt/Window.hs
blob: 5829138e94f7910b313895e8a87e0b19e9710754 (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
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Prompt.Window
-- Copyright   :  Devin Mullins <me@twifkak.com>
--                Andrea Rossato <andrea.rossato@unibz.it>
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  Devin  Mullins <me@twifkak.com>
--                Andrea Rossato <andrea.rossato@unibz.it>
-- Stability   :  unstable
-- Portability :  unportable
--
-- xprompt operations to bring windows to you, and bring you to windows.
--
-----------------------------------------------------------------------------

module XMonad.Prompt.Window
    (
    -- * Usage
    -- $usage 
    windowPromptGoto,
    windowPromptBring
    ) where

import qualified Data.Map as M
import Data.List

import qualified XMonad.StackSet as W
import XMonad
import XMonad.Operations (windows)
import XMonad.Prompt
import XMonad.Actions.WindowBringer

-- $usage
-- WindowPrompt brings windows to you and you to windows.
-- That is to say, it pops up a prompt with window names, in case you forgot
-- where you left your XChat.
--
-- Place in your Config.hs:
--
-- > import XMonad.Prompt
-- > import XMonad.Prompt.Window
--
-- and in the keys definition:
--
-- > , ((modMask x .|. shiftMask, xK_g     ), windowPromptGoto  defaultXPConfig)
-- > , ((modMask x .|. shiftMask, xK_b     ), windowPromptBring defaultXPConfig)

-- %import XMonad.Prompt
-- %import XMonad.Prompt.Window
-- %keybind , ((modMask x .|. shiftMask, xK_g     ), windowPromptGoto  defaultXPConfig)
-- %keybind , ((modMask x .|. shiftMask, xK_b     ), windowPromptBring defaultXPConfig)


data WindowPrompt = Goto | Bring
instance XPrompt WindowPrompt where 
    showXPrompt Goto  = "Go to window:  "
    showXPrompt Bring = "Bring me here:  "

windowPromptGoto, windowPromptBring :: XPConfig -> X ()
windowPromptGoto  c = doPrompt Goto  c
windowPromptBring c = doPrompt Bring c

-- | Pops open a prompt with window titles. Choose one, and you will be
-- taken to the corresponding workspace.
doPrompt :: WindowPrompt -> XPConfig -> X ()
doPrompt t c = do
  a <- case t of
         Goto  -> return . gotoAction  =<< windowMapWith (W.tag . fst)                     
         Bring -> return . bringAction =<< windowMapWith snd
  wm <- windowMapWith id
  mkXPrompt t c (compList wm) a

    where

      winAction a m    = flip whenJust (windows . a) . flip M.lookup m . unescape   
      gotoAction       = winAction W.greedyView
      bringAction      = winAction bringWindow
      bringWindow w ws = W.shiftWin (W.tag . W.workspace . W.current $ ws) w ws

      compList m s = return . filter (isPrefixOf s) . map (escape . fst) . M.toList $ m

      escape []       = []
      escape (' ':xs) = "\\ " ++ escape xs
      escape (x  :xs) = x : escape xs

      unescape []            = []
      unescape ('\\':' ':xs) = ' ' : unescape xs
      unescape (x:xs)        = x   : unescape xs