blob: 2cf26d7955a1522f01d26d46b2318847c4e5f86e (
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
|
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Util.StringProp
-- Copyright : (c) Nicolas Pouillard 2009
-- License : BSD-style (see LICENSE)
--
-- Maintainer : Nicolas Pouillard <nicolas.pouillard@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
-- Internal utility functions for storing Strings with the root window.
--
-- Used for global state like IORefs with string keys, but more latency,
-- persistent between xmonad restarts.
module XMonad.Util.StringProp (
StringProp,
getStringProp, setStringProp,
getStringListProp, setStringListProp,
) where
import XMonad
import Control.Monad(liftM)
import Control.Applicative((<$>))
import Foreign.C.String (castCCharToChar,castCharToCChar)
type StringProp = String
withStringProp :: (MonadIO m) => StringProp -> Display -> (Window -> Atom -> m b) -> m b
withStringProp prop dpy f = do
rootw <- io $ rootWindow dpy $ defaultScreen dpy
a <- io $ internAtom dpy prop False
f rootw a
-- | Set the value of a string property.
setStringProp :: (MonadIO m) => Display -> StringProp -> [Char] -> m ()
setStringProp dpy prop string =
withStringProp prop dpy $ \rootw a ->
io $ changeProperty8 dpy rootw a a propModeReplace $ map castCharToCChar string
-- | Get the name of a string property and returns it as a 'Maybe'.
getStringProp :: (MonadIO m) => Display -> StringProp -> m (Maybe [Char])
getStringProp dpy prop =
withStringProp prop dpy $ \rootw a -> do
p <- io $ getWindowProperty8 dpy a rootw
return $ map castCCharToChar <$> p
-- | Given a property name, returns its contents as a list. It uses the empty
-- list as default value.
getStringListProp :: (MonadIO m) => Display -> StringProp -> m [String]
getStringListProp dpy prop = maybe [] words `liftM` getStringProp dpy prop
-- | Given a property name and a list, sets the value of this property with
-- the list given as argument.
setStringListProp :: (MonadIO m) => Display -> StringProp -> [String] -> m ()
setStringListProp dpy prop str = setStringProp dpy prop (unwords str)
|