aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks
diff options
context:
space:
mode:
authorDmitri Iouchtchenko <johnnyspoon@gmail.com>2013-01-09 03:33:07 +0100
committerDmitri Iouchtchenko <johnnyspoon@gmail.com>2013-01-09 03:33:07 +0100
commita08ca29031158cacb1aa46fbc596ab6fa218c315 (patch)
treebceb1c0cf0f65e820dfed56860ee1502325d517b /XMonad/Hooks
parent16bc07d2c8c87c7693aa49cf4d63cba474712420 (diff)
downloadXMonadContrib-a08ca29031158cacb1aa46fbc596ab6fa218c315.tar.gz
XMonadContrib-a08ca29031158cacb1aa46fbc596ab6fa218c315.tar.xz
XMonadContrib-a08ca29031158cacb1aa46fbc596ab6fa218c315.zip
Add X.H.WorkspaceHistory
Ignore-this: c9e7ce33a944facc27481dde52c7cc80 darcs-hash:20130109023307-7d114-b7e9156b6305334b707b63d04099e08a19bcc058.gz
Diffstat (limited to 'XMonad/Hooks')
-rw-r--r--XMonad/Hooks/WorkspaceHistory.hs74
1 files changed, 74 insertions, 0 deletions
diff --git a/XMonad/Hooks/WorkspaceHistory.hs b/XMonad/Hooks/WorkspaceHistory.hs
new file mode 100644
index 0000000..ed41f42
--- /dev/null
+++ b/XMonad/Hooks/WorkspaceHistory.hs
@@ -0,0 +1,74 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Hooks.WorkspaceHistory
+-- Copyright : (c) 2013 Dmitri Iouchtchenko
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Dmitri Iouchtchenko <johnnyspoon@gmail.com>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Keeps track of workspace viewing order.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Hooks.WorkspaceHistory
+ ( -- * Usage
+ -- $usage
+
+ -- * Hooking
+ workspaceHistoryHook
+
+ -- * Querying
+ , workspaceHistory
+
+ ) where
+
+import XMonad
+import XMonad.StackSet (currentTag)
+import qualified XMonad.Util.ExtensibleState as XS
+
+-- $usage
+-- To record the order in which you view workspaces, you can use this
+-- module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Hooks.WorkspaceHistory (workspaceHistoryHook)
+--
+-- Then add the hook to your 'logHook':
+--
+-- > main = xmonad $ defaultConfig
+-- > { ...
+-- > , logHook = ... >> workspaceHistoryHook >> ...
+-- > , ...
+-- > }
+--
+-- To make use of the collected data, a query function is provided.
+
+data WorkspaceHistory =
+ WorkspaceHistory { history :: [WorkspaceId] -- ^ Workspaces in reverse-chronological order.
+ }
+ deriving (Typeable, Read, Show)
+
+instance ExtensionClass WorkspaceHistory where
+ initialValue = WorkspaceHistory []
+ extensionType = PersistentExtension
+
+-- | A 'logHook' that keeps track of the order in which workspaces have
+-- been viewed.
+workspaceHistoryHook :: X ()
+workspaceHistoryHook = gets (currentTag . windowset) >>= (XS.modify . makeFirst)
+
+-- | A list of workspace tags in the order they have been viewed, with the
+-- most recent first. No duplicates are present, but not all workspaces are
+-- guaranteed to appear, and there may be workspaces that no longer exist.
+workspaceHistory :: X [WorkspaceId]
+workspaceHistory = XS.gets history
+
+
+-- | Cons the 'WorkspaceId' onto the 'WorkspaceHistory' if it is not
+-- already there, or move it to the front if it is.
+makeFirst :: WorkspaceId -> WorkspaceHistory -> WorkspaceHistory
+makeFirst w v = let (xs, ys) = break (w ==) $ history v
+ in v { history = w : (xs ++ drop 1 ys) }