aboutsummaryrefslogtreecommitdiffstats
path: root/DynamicLog.hs
blob: e8d5419577e842beb8cd15d0bf19e0b1f75d3af9 (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
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
-----------------------------------------------------------------------------
-- |
-- 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,
    dynamicLogWithPP,
    dynamicLogXinerama,

    pprWindowSet,
    pprWindowSetXinerama,

    PP(..), defaultPP, sjanssenPP,
    wrap, xmobarColor
  ) 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

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


-- |
-- An example log hook, print a status bar output to stdout, in the form:
--
-- > 1 2 [3] 4 7 : full : title
--
-- That is, the currently populated workspaces, the current
-- workspace layout, and the title of the focused window.
--
dynamicLog :: X ()
dynamicLog = dynamicLogWithPP defaultPP

-- |
-- A log function that uses the 'PP' hooks to customize output.
dynamicLogWithPP :: PP -> X ()
dynamicLogWithPP pp = do
    -- layout description
    ld <- withWindowSet $ return . description . S.layout . S.workspace . S.current
    -- workspace list
    ws <- withWindowSet $ return . pprWindowSet pp
    -- window title
    wt <- withWindowSet $ maybe (return "") (fmap show . getName) . S.peek

    io . putStrLn . sepBy (ppSep pp) . ppOrder pp $
                        [ ws
                        , ppLayout pp ld
                        , ppTitle  pp wt
                        ]

pprWindowSet :: PP -> WindowSet -> String
pprWindowSet pp s =  unwords' $ map 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 = printer pp (S.tag w)
          where printer | S.tag w == this         = ppCurrent
                        | S.tag w `elem` visibles = ppVisible
                        | isJust (S.stack w)      = ppHidden
                        | otherwise               = ppHiddenNoWindows

-- |
-- 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

wrap :: String -> String -> String -> String
wrap l r "" = ""
wrap l r m  = l ++ m ++ r

-- | Intersperse spaces, filtering empty words.
unwords' :: [String] -> String
unwords' = sepBy " "

sepBy :: String -> [String] -> String
sepBy sep = concat . intersperse sep . filter (not . null)

-- TODO dzenColor
xmobarColor :: String -> String -> String -> String
xmobarColor fg bg = wrap t "</fc>"
 where t = concat ["<fc=", fg, if null bg then "" else "," ++ bg, ">"]

-- | The 'PP' type allows the user to customize various behaviors of
-- dynamicLogPP
data PP = PP { ppCurrent, ppVisible
             , ppHidden, ppHiddenNoWindows :: WorkspaceId -> String
             , ppSep :: String
             , ppTitle :: String -> String
             , ppLayout :: String -> String
             , ppOrder :: [String] -> [String] }

-- | The default pretty printing options, as seen in dynamicLog
defaultPP :: PP
defaultPP = PP { ppCurrent         = wrap "[" "]"
               , ppVisible         = wrap "<" ">"
               , ppHidden          = id
               , ppHiddenNoWindows = const ""
               , ppSep             = " : "
               , ppTitle           = const ""
               , ppLayout          = id
               , ppOrder           = id }

-- | The options that sjanssen likes to use, as an example.  Note the use of
-- 'xmobarColor' and the record update on defaultPP
sjanssenPP :: PP
sjanssenPP = defaultPP { ppCurrent = xmobarColor "white" "#ff000000"
                       , ppTitle = xmobarColor "#00ee00" ""
                       , ppOrder = reverse
                       }