aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Monitor.hs
diff options
context:
space:
mode:
authorRoman Cheplyaka <roma@ro-che.info>2008-11-15 11:47:35 +0100
committerRoman Cheplyaka <roma@ro-che.info>2008-11-15 11:47:35 +0100
commit43d7d7cb652d49726f7b83a4088c1bf1b34ec61a (patch)
treedd2c6a860f2d9c3994d4c9ae9a5b37b7e14f9e5f /XMonad/Layout/Monitor.hs
parent48dd33e3e3da47cd3ca7e24303da9b130b7388b6 (diff)
downloadXMonadContrib-43d7d7cb652d49726f7b83a4088c1bf1b34ec61a.tar.gz
XMonadContrib-43d7d7cb652d49726f7b83a4088c1bf1b34ec61a.tar.xz
XMonadContrib-43d7d7cb652d49726f7b83a4088c1bf1b34ec61a.zip
added XMonad.Layout.Monitor
darcs-hash:20081115104735-3ebed-324fd5c577eb7e16915105c35a20673b1d24bbdc.gz
Diffstat (limited to 'XMonad/Layout/Monitor.hs')
-rw-r--r--XMonad/Layout/Monitor.hs131
1 files changed, 131 insertions, 0 deletions
diff --git a/XMonad/Layout/Monitor.hs b/XMonad/Layout/Monitor.hs
new file mode 100644
index 0000000..d46f914
--- /dev/null
+++ b/XMonad/Layout/Monitor.hs
@@ -0,0 +1,131 @@
+{-# 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
+ -- $hints
+
+ -- * TODO
+ -- $todo
+ Property(..),
+ MonitorMessage(..),
+ addMonitor,
+ addPersistentMonitor,
+ addNamedMonitor,
+ addNamedPersistentMonitor
+ ) where
+
+import XMonad
+import XMonad.Layout.LayoutModifier
+import XMonad.Util.WindowProperties
+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 ||| ...
+--
+-- 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 ), sendMessage ToggleMonitor)
+--
+-- 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. Also it's good idea to make it unmanaged and (optionally) hide it using ManageHook:
+--
+-- > className =? "Cairo-clock"--> (ask >>= \w -> liftX (hide w) >> doF (W.delete w))
+--
+-- - If you want monitor to be available on /all/ layouts, there's no point in
+-- hiding it. Also use 'addPersistentMonitor' instead of
+-- 'addMonitor' to avoid unnecessary flickering. You can still toggle
+-- monitor with a keybinding.
+--
+-- - You can use several monitors with nested modifiers. Give them a name using
+-- 'addNamedMonitor' or 'addNamedPersistentMonitor' to be able to toggle
+-- them independently.
+--
+-- - 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