[xmonad] darcs patch: Add Stoppable layout for power saving
Anton Vorontsov
anton at enomsg.org
Thu Aug 28 20:11:53 UTC 2014
On Thu, Aug 28, 2014 at 02:14:03PM -0400, Brandon Allbery wrote:
> On Thu, Aug 28, 2014 at 2:07 PM, Anton Vorontsov <anton at enomsg.org> wrote:
> > To stop the process we use signals, which works for most cases.
>
> Please check WM_CLIENT_MACHINE so you don't try to kill a process not
> running on the same machine xmonad is (ssh forwarding, TCP X server
> connections, etc.)
Yeah, totally makes sense -- I probably don't want to stop random local
processes that happen to share same PID with remote X clients... :)
I'll wait a day or so before resending the full patch, in case there's
more feedback. In the mean time, inlined below are the changes that I'll
incorporate. I'm using the environment variable as I am not sure if
introducing new cabal dependency (hostname package) is a good idea, plus I
see some other xmonad code uses getEnv approach as well...
Thanks,
Anton
diff -rN -u old-XMonadContrib/XMonad/Layout/Stoppable.hs new-XMonadContrib/XMonad/Layout/Stoppable.hs
--- old-XMonadContrib/XMonad/Layout/Stoppable.hs 2014-08-28 12:48:56.397898832 -0700
+++ new-XMonadContrib/XMonad/Layout/Stoppable.hs 2014-08-28 12:48:56.400898832 -0700
@@ -38,11 +38,13 @@
import XMonad
import XMonad.Actions.WithAll
-import XMonad.Util.WindowProperties (getProp32s)
+import XMonad.Util.WindowProperties
import XMonad.StackSet hiding (filter)
import XMonad.Layout.LayoutModifier
+import System.Posix.Env
import System.Posix.Signals
import Data.Maybe
+import Control.Monad
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -62,6 +64,11 @@
pid <- getProp32s "_NET_WM_PID" w
io $ (signalProcess s . fromIntegral) `mapM_` fromMaybe [] pid
+signalLocalWindow :: Signal -> Window -> X ()
+signalLocalWindow s w = do
+ host <- io $ getEnvDefault "HOSTNAME" ""
+ hasProperty (Machine host) w >>= flip when (signalWindow s w)
+
withAllOn :: (a -> X ()) -> Workspace i l a -> X ()
withAllOn f wspc = f `mapM_` integrate' (stack wspc)
@@ -73,7 +80,7 @@
sigStoppableWorkspacesHook :: String -> X ()
sigStoppableWorkspacesHook k = do
ws <- gets windowset
- withAllFiltered isStoppable (hidden ws) (signalWindow sigSTOP)
+ withAllFiltered isStoppable (hidden ws) (signalLocalWindow sigSTOP)
where
isStoppable ws = k `elem` words (description $ layout ws)
@@ -84,7 +91,7 @@
instance LayoutModifier Stoppable Window where
modifierDescription = mark
- hook _ = withAll $ signalWindow sigCONT
+ hook _ = withAll $ signalLocalWindow sigCONT
unhook l = sigStoppableWorkspacesHook (mark l)
-- | Convert a layout to a stoppable layout using the default mark
More information about the xmonad
mailing list