[xmonad] [patch] WorkspaceByPos

Adam Vogt vogt.adam at gmail.com
Thu Oct 1 16:26:27 EDT 2009


I've applied the original patch., and my translation to use ErrorT.

It seems to work as the original.

Thanks,
Adam

* On Wednesday, September 30 2009, Adam Vogt wrote:

>* On Wednesday, September 30 2009, Jan Vornberger wrote:
>
>>Hi there!
>>
>>I would like to ask for some comments/tips for improvements on the
>>attached patch.
>>
>>It probably could use the Maybe monad to avoid all those if/thens, but
>>I'm still a little bit unsure when it comes to using two monads at the
>>same time (here the X monad and the Maybe monad). So how would this work
>>here?
>>
>>Also, someone mentioned that it might be better to look at the gravity
>>of the window to figure out if it requested a specifiy geometry, instead
>>of checking for non-zero position. Does anyone have more details on how
>>exactly I would do this?
>>
>>Thx in advance!
>>
>>Jan
>
>This looks like a use for MaybeT or ErrorT, the latter needs a type
>annotation but `asTypeOf` makes this pretty painless:
>
>I did not test that this translation is the same, but it should be ok.
>
>] module XMonad.Hooks.WorkspaceByPos (
>]     -- * Usage
>]     -- $usage
>]     workspaceByPos
>]     ) where
>] 
>] import XMonad
>] import qualified XMonad.StackSet as W
>] import XMonad.Util.XUtils (fi)
>] 
>] import Data.Maybe
>] import Control.Applicative((<$>))
>] import Control.Monad.Error ((<=<),guard,lift,runErrorT,throwError)
>] 
>] -- $usage
>] -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
>] --
>] -- > import XMonad.Hooks.WorkspaceByPos
>] -- >
>] -- > myManageHook = workspaceByPos <+> manageHook defaultConfig
>] -- >
>] -- > main = xmonad defaultConfig { manageHook = myManageHook }
>] 
>] workspaceByPos :: ManageHook
>] workspaceByPos = (maybe idHook doShift <=< liftX . needsMoving) =<< ask
>] 
>] needsMoving :: Window -> X (Maybe WorkspaceId)
>] needsMoving w = withDisplay $ \d -> do
>]     -- only relocate windows with non-zero position
>]     wa <- io $ getWindowAttributes d w
>]     fmap (const Nothing `either` Just) . runErrorT $ do
>]         guard $ wa_x wa == 0 && wa_y wa == 0
>]         ws <- gets windowset
>]         sc <- lift $ fromMaybe (W.current ws)
>]                 <$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
>]         Just wkspc <- lift $ screenWorkspace (W.screen sc)
>]         guard $ W.currentTag ws /= wkspc
>]         return wkspc `asTypeOf` throwError ""


More information about the xmonad mailing list