aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Monitor.hs
blob: 24dbf2643bb609e80d6d4e742a13069b19faa48b (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
{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.Monitor
-- Copyright   :  (c) Roman Cheplyaka
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  Roman Cheplyaka <roma@ro-che.info>
-- Stability   :  unstable
-- Portability :  unportable
--
-- Layout modfier for displaying some window (monitor) above other windows
--
-----------------------------------------------------------------------------
module XMonad.Layout.Monitor (
    -- * Usage
    -- $usage

    -- * Hints and issues
    -- $hints

    -- * TODO
    -- $todo
    Property(..),
    MonitorMessage(..),
    addMonitor,
    addPersistentMonitor,
    addNamedMonitor,
    addNamedPersistentMonitor,
    doHideIgnore
    ) where

import XMonad
import XMonad.Layout.LayoutModifier
import XMonad.Util.WindowProperties
import XMonad.Hooks.ManageHelpers (doHideIgnore)
import Control.Monad

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.Monitor
--
-- Then add monitor to desired layouts:
--
-- > myLayouts = addMonitor (ClassName "Cairo-clock" `And` Title "MacSlow's Cairo-Clock") (Rectangle (1280-150) (800-150) 150 150) $ tall ||| Full ||| ...
-- 
-- And make the desired window unmanaged with ManageHook:
--
-- > , className =? "Cairo-clock"--> doIgnore
--
-- After that, if there exists a window with specified properties, it will be
-- displayed on top of all /tiled/ (not floated) windows on specified
-- position.
--
-- It's also useful to add some keybinding to toggle monitor visibility:
-- 
-- > , ((mod1Mask, xK_u     ), broadcastMessage ToggleMonitor >> refresh)
--
-- Screenshot: <http://www.haskell.org/haskellwiki/Image:Xmonad-clock.png>

data Monitor a = Monitor {
    prop :: Property, -- a window which satisfies that property is chosen as monitor
    rect :: Rectangle, -- where to put monitor
    visible :: Bool, -- is it visible?
    mbName :: (Maybe String), -- name of monitor (useful when we have many of them)
    persistent :: Bool -- on all layouts?
    } deriving (Read, Show)

data MonitorMessage = ToggleMonitor | ShowMonitor | HideMonitor
                    | ToggleMonitorNamed String
                    | ShowMonitorNamed String
                    | HideMonitorNamed String
    deriving (Read,Show,Eq,Typeable)
instance Message MonitorMessage

withMonitor :: Property -> a -> (Window -> X a) -> X a
withMonitor p a fn = do
    monitorWindows <- allWithProperty p
    case monitorWindows of
        [] -> return a
        w:_ -> fn w

instance LayoutModifier Monitor Window where
    redoLayout mon _ _ rects = withMonitor (prop mon) (rects, Nothing) $ \w ->
        if visible mon
            then do tileWindow w (rect mon)
                    reveal w
                    return ((w,rect mon):rects, Nothing)
            else do hide w
                    return (rects, Nothing)
    handleMess mon mess
        | Just ToggleMonitor <- fromMessage mess = return $ Just $ mon { visible = not $ visible mon }
        | Just (ToggleMonitorNamed n) <- fromMessage mess = return $
            if mbName mon `elem` [Just n, Nothing] then Just $ mon { visible = not $ visible mon } else Nothing
        | Just ShowMonitor <- fromMessage mess = return $ Just $ mon { visible = True }
        | Just (ShowMonitorNamed n) <- fromMessage mess = return $
            if mbName mon `elem` [Just n, Nothing] then Just $ mon { visible = True } else Nothing
        | Just HideMonitor <- fromMessage mess = return $ Just $ mon { visible = False }
        | Just (HideMonitorNamed n) <- fromMessage mess = return $
            if mbName mon `elem` [Just n, Nothing] then Just $ mon { visible = False } else Nothing
        | Just Hide <- fromMessage mess = do unless (persistent mon) $ withMonitor (prop mon) () hide; return Nothing
        | otherwise = return Nothing
        
addMonitor :: Property -> Rectangle -> l a -> ModifiedLayout Monitor l a
addMonitor p r = ModifiedLayout (Monitor p r True Nothing False)
addPersistentMonitor :: Property -> Rectangle -> l a -> ModifiedLayout Monitor l a
addPersistentMonitor p r = ModifiedLayout (Monitor p r True Nothing True)
addNamedMonitor :: String -> Property -> Rectangle -> l a -> ModifiedLayout Monitor l a
addNamedMonitor name p r = ModifiedLayout (Monitor p r True (Just name) False)
addNamedPersistentMonitor :: String -> Property -> Rectangle -> l a -> ModifiedLayout Monitor l a
addNamedPersistentMonitor name p r = ModifiedLayout (Monitor p r True (Just name) True)

-- $hints
-- - This module assumes that there is only one window satisfying property exists.
--
-- - If you want the monitor to be available on /all/ layouts, use
-- 'addPersistentMonitor' instead of 'addMonitor' to avoid unnecessary
-- flickering. You can still toggle monitor with a keybinding.
--
-- - On the other hand, if you use the monitor only with some of the layouts, you
-- might want to hide it on the startup. Then change ManageHook to the following:
--
-- > className =? "Cairo-clock"--> (ask >>= \w -> liftX (hide w) >> doF (W.delete w))
--
-- - You can use several monitors with nested modifiers. Give them a name using
-- 'addNamedMonitor' or 'addNamedPersistentMonitor' to be able to toggle
-- them independently.
--
-- - To make monitor transparent, import "XMonad.Hooks.FadeInactive" and change
-- ManageHook to (@0xAAAAAAAA@ is the level of opacity):
--
-- > className =? "Cairo-clock"--> (ask >>= liftX . flip setOpacity 0xAAAAAAAA >> doIgnore)
--
-- - You can display monitor only on specific workspaces with
-- "XMonad.Layout.PerWorkspace".

-- $todo
-- - make Monitor remember the window it manages
--
-- - automatically unmanage the window?
-- 
-- - specify position relative to the screen