[xmonad] darcs patch: add XMonad.Hooks.PlaceNext

Brent Yorgey byorgey at seas.upenn.edu
Mon Jun 28 04:27:18 EDT 2010


Oops, sorry, I see you changed this in your more recent patch.

-Brent

On Mon, Jun 28, 2010 at 09:25:55AM +0100, Brent Yorgey wrote:
> For keeping state, is there a reason you need to use MVars and
> unsafePerformIO rather than XMonad.Util.ExtensibleState?
> 
> -Brent
> 
> On Wed, Jun 23, 2010 at 08:34:53PM -0400, Ben Boeckel wrote:
> > Hi,
> > 
> > I found FloatNext recently and thought it'd be useful to do something
> > similar with where the next window gets placed. I also found
> > InsertPosition which did what I wanted, but not conditionally. The new
> > hook is a wrapper around InsertPosition that utilises FloatNext's
> > conditional ability. Feedback welcome.
> > 
> > --Ben
> 
> > [add-hooks-placenext
> > mathstuf at gmail.com**20100624000718
> >  Ignore-this: c293bd954de3045729161a7dca1df14a
> >  
> >  Add hook that works similar to FloatNext and wraps InsertPosition to allow the
> >  user to mark that the next (or all future) windows should pop up above or below
> >  the current window and whether it should be focused or not. It supplies
> >  keybinding functions to toggle the state of each of the flags and a function to
> >  force running the log hook (named differently to avoid clashing with
> >  FloatNext).
> > ] {
> > addfile ./XMonad/Hooks/PlaceNext.hs
> > hunk ./XMonad/Hooks/PlaceNext.hs 1
> > +-----------------------------------------------------------------------------
> > +-- |
> > +-- Module      :  XMonad.Hooks.PlaceNext
> > +-- Copyright   :  Ben Boeckel <mathstuf at gmail.com>
> > +-- License     :  BSD-style (see LICENSE)
> > +--
> > +-- Maintainer  :  Ben Boeckel <mathstuf at gmail.com>
> > +-- Stability   :  unstable
> > +-- Portability :  unportable
> > +--
> > +-- Hook and keybindings for determining where the next
> > +-- window(s) will be placed.
> > +-----------------------------------------------------------------------------
> > +
> > +module XMonad.Hooks.PlaceNext ( -- * Usage
> > +                                -- $usage
> > +
> > +                                -- * The hook
> > +                                placeNextHook
> > +
> > +                                -- * Actions
> > +                              , placeNextBelow
> > +                              , togglePlaceNextBelow
> > +                              , placeAllNewBelow
> > +                              , togglePlaceAllNewBelow
> > +                              , unfocusNext
> > +                              , toggleUnfocusNext
> > +                              , unfocusAllNew
> > +                              , toggleUnfocusAllNew
> > +
> > +                                -- * Queries
> > +                              , willPlaceNextBelow
> > +                              , willPlaceAllNewBelow
> > +                              , willUnfocusNext
> > +                              , willUnfocusAllNew
> > +
> > +                                -- * 'DynamicLog' utilities
> > +                                -- $pp
> > +                              , wherePlaceNextPP
> > +                              , wherePlaceAllNewPP
> > +                              , willUnfocusNextPP
> > +                              , willUnfocusAllNewPP
> > +                              , runLogHookPlace ) where
> > +
> > +import Prelude hiding (all)
> > +
> > +import XMonad
> > +
> > +import XMonad.Hooks.InsertPosition
> > +
> > +import Control.Monad (join)
> > +import Control.Applicative ((<$>))
> > +import Control.Arrow (first, second)
> > +import Control.Concurrent.MVar
> > +import System.IO.Unsafe (unsafePerformIO)
> > +
> > +
> > +{- Helper functions -}
> > +
> > +modifyMVar2 :: MVar a -> (a -> a) -> IO ()
> > +modifyMVar2 v f = modifyMVar_ v (return . f)
> > +
> > +_set :: ((a -> a) -> ((Bool, Bool), (Bool, Bool)) -> ((Bool, Bool), (Bool, Bool))) -> a -> X ()
> > +_set f b = io $ modifyMVar2 placeModeMVar (f $ const b)
> > +
> > +_toggle :: ((Bool -> Bool) -> ((Bool, Bool), (Bool, Bool)) -> ((Bool, Bool), (Bool, Bool))) -> X ()
> > +_toggle f = io $ modifyMVar2 placeModeMVar (f not)
> > +
> > +_get :: (((Bool, Bool), (Bool, Bool)) -> a) -> X a
> > +_get f = io $ f <$> readMVar placeModeMVar
> > +
> > +_pp :: (((Bool, Bool), (Bool, Bool)) -> Bool) -> String -> (String -> String) -> X (Maybe String)
> > +_pp f s st = _get f >>= \b -> if b then return $ Just $ st s else return Nothing
> > +
> > +
> > +{- The current state is kept here -}
> > +
> > +placeModeMVar :: MVar ((Bool, Bool), (Bool, Bool))
> > +placeModeMVar = unsafePerformIO $ newMVar ((False, False), (False, False))
> > +
> > +
> > +-- $usage
> > +-- This module provides actions (that can be set as keybindings)
> > +-- to automatically send the next spawned window(s) to be a place.
> > +--
> > +-- You can use it by including the following in your @~\/.xmonad\/xmonad.hs@:
> > +--
> > +-- > import XMonad.Hooks.placeNext
> > +--
> > +-- and adding 'placeNextHook' to your 'ManageHook':
> > +--
> > +-- > myManageHook = placeNextHook <+> manageHook defaultConfig
> > +--
> > +-- The 'placeNext' and 'toggleplaceNext' functions can be used in key
> > +-- bindings to place the next spawned window:
> > +--
> > +-- > , ((modm, xK_e), toggleplaceNext)
> > +--
> > +-- 'placeAllNew' and 'toggleplaceAllNew' are similar but place all
> > +-- spawned windows until disabled again.
> > +--
> > +-- > , ((modm, xK_r), toggleplaceAllNew)
> > +
> > +
> > +-- | This 'ManageHook' will selectively place windows as set
> > +-- by 'placeNext' and 'placeAllNew'.
> > +placeNextHook :: ManageHook
> > +placeNextHook = do (next, all) <- io $ takeMVar placeModeMVar
> > +                   io $ putMVar placeModeMVar ((False, False), all)
> > +                   pos <- return $ if (fst next) || (fst all) then Below else Above
> > +                   fcs <- return $ if (snd next) || (snd all) then Older else Newer
> > +                   insertPosition pos fcs
> > +
> > +
> > +-- | @placeNextBelow True@ arranges for the next spawned window to be
> > +-- placed under the current window, @placeNextBelow False@ cancels it.
> > +placeNextBelow :: Bool -> X ()
> > +placeNextBelow = _set (first . first)
> > +
> > +togglePlaceNextBelow :: X ()
> > +togglePlaceNextBelow = _toggle (first . first)
> > +
> > +-- | @placeAllNewBelow True@ arranges for new windows to be
> > +-- placed under the current window, @placeAllNewBelow False@ cancels it
> > +placeAllNewBelow :: Bool -> X ()
> > +placeAllNewBelow = _set (second . first)
> > +
> > +togglePlaceAllNewBelow :: X ()
> > +togglePlaceAllNewBelow = _toggle (second . first)
> > +
> > +
> > +-- | @unfocusNext True@ arranges for the next spawned window to be
> > +-- unfocused, @unfocusNext False@ cancels it.
> > +unfocusNext :: Bool -> X ()
> > +unfocusNext = _set (first . second)
> > +
> > +toggleUnfocusNext :: X ()
> > +toggleUnfocusNext = _toggle (first . second)
> > +
> > +-- | @unfocusAllNew True@ arranges for new windows to be
> > +-- unfocused, @unfocusAllNew False@ cancels it
> > +unfocusAllNew :: Bool -> X ()
> > +unfocusAllNew = _set (second . first)
> > +
> > +toggleUnfocusAllNew :: X ()
> > +toggleUnfocusAllNew = _toggle (second . second)
> > +
> > +
> > +-- | Whether the next window will be placed below the current window
> > +willPlaceNextBelow :: X Bool
> > +willPlaceNextBelow = _get (fst . fst)
> > +
> > +-- | Whether new windows will be placed below the current window
> > +willPlaceAllNewBelow :: X Bool
> > +willPlaceAllNewBelow = _get (fst . snd)
> > +
> > +
> > +-- | Whether the next window will be unfocused or not
> > +willUnfocusNext :: X Bool
> > +willUnfocusNext = _get (snd . fst)
> > +
> > +-- | Whether new windows will be unfocused or not
> > +willUnfocusAllNew :: X Bool
> > +willUnfocusAllNew = _get (snd . snd)
> > +
> > +
> > +-- $pp
> > +-- The following functions are used to display the current
> > +-- state of 'placeNext' and 'placeAllNew' in your
> > +-- 'XMonad.Hooks.DynamicLog.dynamicLogWithPP'.
> > +-- 'wherePlaceNextPP' and 'wherePlaceAllNewPP' should be added
> > +-- to the 'XMonad.Hooks.DynamicLog.ppExtras' field of your
> > +-- 'XMonad.Hooks.DynamicLog.PP'.
> > +--
> > +-- Use 'runLogHook' to refresh the output of your 'logHook', so
> > +-- that the effects of a 'placeNext'/... will be visible
> > +-- immediately:
> > +--
> > +-- > , ((modm, xK_e), toggleplaceNext >> runLogHook)
> > +--
> > +-- The @String -> String@ parameters to 'willplaceNextPP' and
> > +-- 'willplaceAllNewPP' will be applied to their output, you
> > +-- can use them to set the text color, etc., or you can just
> > +-- pass them 'id'.
> > +
> > +wherePlaceNextPP :: (String -> String) -> X (Maybe String)
> > +wherePlaceNextPP = _pp (fst . fst) "Next"
> > +
> > +wherePlaceAllNewPP :: (String -> String) -> X (Maybe String)
> > +wherePlaceAllNewPP = _pp (fst . snd) "All"
> > +
> > +willUnfocusNextPP :: (String -> String) -> X (Maybe String)
> > +willUnfocusNextPP = _pp (snd . fst) "Next"
> > +
> > +willUnfocusAllNewPP :: (String -> String) -> X (Maybe String)
> > +willUnfocusAllNewPP = _pp (snd . snd) "All"
> > +
> > +runLogHookPlace :: X ()
> > +runLogHookPlace = join $ asks $ logHook . config
> > hunk ./xmonad-contrib.cabal 149
> > +                        XMonad.Hooks.PlaceNext
> > }
> 
> 
> 
> 
> > _______________________________________________
> > xmonad mailing list
> > xmonad at haskell.org
> > http://www.haskell.org/mailman/listinfo/xmonad
> 
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad


More information about the xmonad mailing list