aboutsummaryrefslogtreecommitdiffstats
path: root/DynamicLog.hs
blob: d2ad23b256b671c0e71b82a75fb550e6b73262ac (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
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonadContrib.DynamicLog
-- Copyright   :  (c) Don Stewart <dons@cse.unsw.edu.au>
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Don Stewart <dons@cse.unsw.edu.au>
-- Stability   :  unstable
-- Portability :  unportable
--
-- DynamicLog
--
-- Log events in:
--
-- >     1 2 [3] 4 8
--
-- format. Suitable to pipe into dzen.
--
-----------------------------------------------------------------------------

module XMonadContrib.DynamicLog (
    -- * Usage
    -- $usage 
    dynamicLog, dynamicLogWithTitle, dynamicLogWithTitleColored, dynamicLogXinerama, pprWindowSet, pprWindowSetXinerama
  ) where

-- 
-- Useful imports
--
import XMonad
import {-# SOURCE #-} Config (workspaces)
import Operations () -- for ReadableSomeLayout instance
import Data.Maybe ( isJust )
import Data.List
import Data.Ord ( comparing )
import qualified StackSet as S
import Data.Monoid
import XMonadContrib.NamedWindows

-- $usage 
--
-- To use, set:
--
-- >    import XMonadContrib.DynamicLog
-- >    logHook = dynamicLog
--
-- To get the title of the currently focused window after the workspace list:
--
-- >    import XMonadContrib.DynamicLog
-- >    logHook = dynamicLogWithTitle
--
-- To have the window title highlighted in any color recognized by dzen:
--
-- >    import XMonadContrib.DynamicLog
-- >    logHook = dynamicLogWithTitleColored "white"
--

-- %import XMonadContrib.DynamicLog
-- %def -- comment out default logHook definition above if you uncomment any of these:
-- %def logHook = dynamicLog
-- %def logHook = dynamicLogWithTitle
-- %def logHook = dynamicLogWithTitleColored "white"


-- |
-- Perform an arbitrary action on each state change.
-- Examples include:
--      * do nothing
--      * log the state to stdout
--
-- An example logger, print a status bar output to dzen, in the form:
--
-- > 1 2 [3] 4 7
--  

dynamicLog :: X ()
dynamicLog = withWindowSet $ \ws -> do
    let desc = description . S.layout . S.workspace . S.current $ ws
    io . putStrLn $ "(" ++ desc ++ ") " ++ pprWindowSet ws

-- Appends title of currently focused window to log output
-- Arguments are: pre-title text and post-title text
dynamicLogWithTitle_ :: String -> String -> X ()
dynamicLogWithTitle_ pre post= do ld <- withWindowSet $ return . description . S.layout . S.workspace . S.current  -- layout description
                                  ws <- withWindowSet $ return . pprWindowSet  -- workspace list
                                  wt <- withWindowSet $ maybe (return "") (fmap show . getName) . S.peek  -- window title
                                  io . putStrLn $ "(" ++ ld ++ ") " ++ ws ++ " " ++ pre ++ wt ++ post

dynamicLogWithTitle :: X ()
dynamicLogWithTitle = dynamicLogWithTitle_ "<" ">"

-- As dynamicLogWithTitle but with colored window title instead of angle brackets (works with dzen only)
dynamicLogWithTitleColored :: String -> X ()
dynamicLogWithTitleColored color = dynamicLogWithTitle_ ("^fg(" ++ color ++ ")") "^fg()"

pprWindowSet :: WindowSet -> String
pprWindowSet s =  concatMap fmt $ sortBy cmp
            (map S.workspace (S.current s : S.visible s) ++ S.hidden s)
   where f Nothing Nothing = EQ
         f (Just _) Nothing = LT
         f Nothing (Just _) = GT
         f (Just x) (Just y) = compare x y

         wsIndex = flip elemIndex workspaces . S.tag

         cmp a b = f (wsIndex a) (wsIndex b) `mappend` compare (S.tag a) (S.tag b)

         this     = S.tag (S.workspace (S.current s))
         visibles = map (S.tag . S.workspace) (S.visible s)

         fmt w | S.tag w == this         = "[" ++ S.tag w ++ "]"
               | S.tag w `elem` visibles = "<" ++ S.tag w ++ ">"
               | isJust (S.stack w)      = " " ++ S.tag w ++ " "
               | otherwise               = ""

-- |
-- Workspace logger with a format designed for Xinerama:
--
-- > [1 9 3] 2 7
--
-- where 1, 9, and 3 are the workspaces on screens 1, 2 and 3, respectively,
-- and 2 and 7 are non-visible, non-empty workspaces
--
dynamicLogXinerama :: X ()
dynamicLogXinerama = withWindowSet $ io . putStrLn . pprWindowSetXinerama

pprWindowSetXinerama :: WindowSet -> String
pprWindowSetXinerama ws = "[" ++ unwords onscreen ++ "] " ++ unwords offscreen
  where onscreen  = map (S.tag . S.workspace)
                        . sortBy (comparing S.screen) $ S.current ws : S.visible ws
        offscreen = map S.tag . filter (isJust . S.stack)
                        . sortBy (comparing S.tag) $ S.hidden ws