mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
From A.Topicspace split functions for storing strings with root to U.StringProp
These functions will be used to send strings for execution by command line, in xmonad-eval
This commit is contained in:
parent
9847e0da5e
commit
2d84da7fdd
@ -172,13 +172,10 @@ import Data.List
|
|||||||
import Data.Maybe (fromMaybe, isNothing, listToMaybe)
|
import Data.Maybe (fromMaybe, isNothing, listToMaybe)
|
||||||
import Data.Ord
|
import Data.Ord
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Graphics.X11.Xlib
|
|
||||||
import Control.Monad ((=<<),liftM2,when,unless,replicateM_)
|
import Control.Monad ((=<<),liftM2,when,unless,replicateM_)
|
||||||
import System.IO
|
import System.IO
|
||||||
import Foreign.C.String (castCCharToChar,castCharToCChar)
|
|
||||||
|
|
||||||
import XMonad.Operations
|
import XMonad.Operations
|
||||||
import Control.Applicative ((<$>))
|
|
||||||
import qualified XMonad.StackSet as W
|
import qualified XMonad.StackSet as W
|
||||||
|
|
||||||
import XMonad.Prompt
|
import XMonad.Prompt
|
||||||
@ -189,6 +186,7 @@ import XMonad.Hooks.DynamicLog (PP(..))
|
|||||||
import qualified XMonad.Hooks.DynamicLog as DL
|
import qualified XMonad.Hooks.DynamicLog as DL
|
||||||
|
|
||||||
import XMonad.Util.Run (spawnPipe)
|
import XMonad.Util.Run (spawnPipe)
|
||||||
|
import XMonad.Util.StringProp(getStringListProp,setStringListProp)
|
||||||
|
|
||||||
-- | An alias for @flip replicateM_@
|
-- | An alias for @flip replicateM_@
|
||||||
(>*>) :: Monad m => m a -> Int -> m ()
|
(>*>) :: Monad m => m a -> Int -> m ()
|
||||||
@ -220,16 +218,16 @@ data TopicConfig = TopicConfig { topicDirs :: M.Map Topic Dir
|
|||||||
-- | Returns the list of last focused workspaces the empty list otherwise.
|
-- | Returns the list of last focused workspaces the empty list otherwise.
|
||||||
-- This function rely on a reserved property namely _XMONAD_LAST_FOCUSED_WORKSPACES.
|
-- This function rely on a reserved property namely _XMONAD_LAST_FOCUSED_WORKSPACES.
|
||||||
getLastFocusedTopics :: X [String]
|
getLastFocusedTopics :: X [String]
|
||||||
getLastFocusedTopics = getStringListProp "_XMONAD_LAST_FOCUSED_WORKSPACES"
|
getLastFocusedTopics = asks display >>= flip getStringListProp "_XMONAD_LAST_FOCUSED_WORKSPACES"
|
||||||
|
|
||||||
-- | Given a 'TopicConfig', the last focused topic, and a predicate that will
|
-- | Given a 'TopicConfig', the last focused topic, and a predicate that will
|
||||||
-- select topics that one want to keep, this function will set the property
|
-- select topics that one want to keep, this function will set the property
|
||||||
-- of last focused topics.
|
-- of last focused topics.
|
||||||
setLastFocusedTopic :: TopicConfig -> Topic -> (Topic -> Bool) -> X ()
|
setLastFocusedTopic :: TopicConfig -> Topic -> (Topic -> Bool) -> X ()
|
||||||
setLastFocusedTopic tg w predicate =
|
setLastFocusedTopic tg w predicate = do
|
||||||
getLastFocusedTopics >>=
|
disp <- asks display
|
||||||
setStringListProp "_XMONAD_LAST_FOCUSED_WORKSPACES"
|
setStringListProp disp "_XMONAD_LAST_FOCUSED_WORKSPACES"
|
||||||
. take (maxTopicHistory tg) . nub . (w:) . filter predicate
|
. take (maxTopicHistory tg) . nub . (w:) . filter predicate =<< getLastFocusedTopics
|
||||||
|
|
||||||
-- | This function is a variant of 'DL.pprWindowSet' which takes a topic configuration
|
-- | This function is a variant of 'DL.pprWindowSet' which takes a topic configuration
|
||||||
-- and a pretty-printing record 'PP'. It will show the list of topics sorted historically
|
-- and a pretty-printing record 'PP'. It will show the list of topics sorted historically
|
||||||
@ -301,42 +299,9 @@ checkTopicConfig tags tg = do
|
|||||||
check diffTopic "Seen but missing topics/workspaces"
|
check diffTopic "Seen but missing topics/workspaces"
|
||||||
check dups "Duplicate topics/workspaces"
|
check dups "Duplicate topics/workspaces"
|
||||||
|
|
||||||
type StringProp = String
|
|
||||||
|
|
||||||
withStringProp :: StringProp -> (Display -> Window -> Atom -> X a) -> X a
|
|
||||||
withStringProp prop f =
|
|
||||||
withDisplay $ \dpy -> do
|
|
||||||
rootw <- asks theRoot
|
|
||||||
a <- io $ internAtom dpy prop False
|
|
||||||
f dpy rootw a
|
|
||||||
|
|
||||||
-- | Get the name of a string property and returns it as a 'Maybe'.
|
|
||||||
getStringProp :: StringProp -> X (Maybe String)
|
|
||||||
getStringProp prop =
|
|
||||||
withStringProp prop $ \dpy rootw a -> do
|
|
||||||
p <- io $ getWindowProperty8 dpy a rootw
|
|
||||||
return $ map castCCharToChar <$> p
|
|
||||||
|
|
||||||
-- | Set the value of a string property.
|
|
||||||
setStringProp :: StringProp -> String -> X ()
|
|
||||||
setStringProp prop string =
|
|
||||||
withStringProp prop $ \dpy rootw a ->
|
|
||||||
io $ changeProperty8 dpy rootw a a propModeReplace $ map castCharToCChar string
|
|
||||||
|
|
||||||
-- | Given a property name, returns its contents as a list. It uses the empty
|
|
||||||
-- list as default value.
|
|
||||||
getStringListProp :: StringProp -> X [String]
|
|
||||||
getStringListProp prop = return . maybe [] words =<< getStringProp prop
|
|
||||||
|
|
||||||
-- | Given a property name and a list, sets the value of this property with
|
|
||||||
-- the list given as argument.
|
|
||||||
setStringListProp :: StringProp -> [String] -> X ()
|
|
||||||
setStringListProp prop = setStringProp prop . unwords
|
|
||||||
|
|
||||||
-- | Display the given message using the @xmessage@ program.
|
-- | Display the given message using the @xmessage@ program.
|
||||||
xmessage :: String -> IO ()
|
xmessage :: String -> IO ()
|
||||||
xmessage s = do
|
xmessage s = do
|
||||||
h <- spawnPipe "xmessage -file -"
|
h <- spawnPipe "xmessage -file -"
|
||||||
hPutStr h s
|
hPutStr h s
|
||||||
hClose h
|
hClose h
|
||||||
|
|
||||||
|
56
XMonad/Util/StringProp.hs
Normal file
56
XMonad/Util/StringProp.hs
Normal file
@ -0,0 +1,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)
|
@ -213,6 +213,7 @@ library
|
|||||||
XMonad.Util.Loggers
|
XMonad.Util.Loggers
|
||||||
XMonad.Util.NamedScratchpad
|
XMonad.Util.NamedScratchpad
|
||||||
XMonad.Util.NamedWindows
|
XMonad.Util.NamedWindows
|
||||||
|
XMonad.Util.StringProp
|
||||||
XMonad.Util.Run
|
XMonad.Util.Run
|
||||||
XMonad.Util.Scratchpad
|
XMonad.Util.Scratchpad
|
||||||
XMonad.Util.Themes
|
XMonad.Util.Themes
|
||||||
|
Loading…
x
Reference in New Issue
Block a user