
Hit send before I had checked the headers, and it only went to Daniel.
Sorry for the extra mail, Daniel.
---------- Forwarded message ----------
From: Mike Meyer
Excerpts from Mike Meyer's message of 2014-09-23 07:31:08 -0700:
The Message is called "SplitMaster", and has no arguments. It sets the client count of the master pane to 1 if it's not currently 1, thus providing a quick way to get back to that setting. It setgs the client count for the master pane to 2 if it's currently 1, effectively making it a toggle between the two modes of a split master pane and an full size master pane.
Can this be done entirely from the configuration? For example, a low-tech solution would be to simply have two Tall layouts in your layout hook (one with one master pane and one with two master panes) and a keybinding that toggles between them, e.g. using X.A.CycleSelectedLayouts [1].
I recognize that this is not *identical*, but perhaps it's close to your needs and doesn't require changes xmonad's corej
After thinking about it some, I would say using multiple Layouts won't work - but I'm not an expert. The problem for me is that I actually use multiple Layouts, and switching between them is a conceptually different thing from switching between one and two clients in the master pane. So using an extra layout for this would create extra steps when I wanted to change the number of clients in the master pane AND when I wanted to change layouts. I think I'd rather have the current behavior. If someone wants o Is there some way to have a configuration with two sets of layouts to toggle between? that would certainly do the trick. While I can see how to do that, I'm not sure it's in general a good idea and so suspect it's not there.

On Wed, Oct 1, 2014 at 6:10 PM, Mike Meyer
Is there some way to have a configuration with two sets of layouts to toggle between? that would certainly do the trick. While I can see how to do that, I'm not sure it's in general a good idea and so suspect it's not there.
I don't recall one pre-existing offhand, but there is certainly no reason you couldn't. For example, copy (XMonad.Layout.|||) and substitute your own message for NextLayout. Use it to combine layout groups; now mod-space moves within a layout group and a binding to send your new message cycles between layout groups. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I think another option is to make a new instance of LayoutClass that is
just like Tall except for also supporting this message. In fact, you should
be able to delegate to Tall for most definitions. Just writing off the cuff
- could be wrong.
On Oct 1, 2014 3:16 PM, "Brandon Allbery"
On Wed, Oct 1, 2014 at 6:10 PM, Mike Meyer
wrote: Is there some way to have a configuration with two sets of layouts to toggle between? that would certainly do the trick. While I can see how to do that, I'm not sure it's in general a good idea and so suspect it's not there.
I don't recall one pre-existing offhand, but there is certainly no reason you couldn't. For example, copy (XMonad.Layout.|||) and substitute your own message for NextLayout. Use it to combine layout groups; now mod-space moves within a layout group and a binding to send your new message cycles between layout groups.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad

On Wed, Oct 1, 2014 at 7:03 PM, Devin Mullins
I think another option is to make a new instance of LayoutClass that is just like Tall except for also supporting this message. In fact, you should be able to delegate to Tall for most definitions. Just writing off the cuff - could be wrong.
Delegating to Tall won't work; you'd have to copy the definition and modify it, like I suggested for (|||). -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

This can totally be done from your config only without having to modify the
core of Xmonad. I found this to be an interesting problem and slapped
together a solution that uses XMonad.Util.ExtensibleState.
I added the following to my xmonad.hs:
import qualified XMonad.Util.ExtensibleState as XS
.....
.....
data MasterPaneFlag = MasterPaneFlag { getFlag :: Bool }
deriving (Show, Typeable)
instance ExtensionClass MasterPaneFlag where
initialValue = MasterPaneFlag False
pickIncrFun :: Bool -> X ()
pickIncrFun flag = if flag then (sendMessage (IncMasterN (-1))) else
(sendMessage (IncMasterN 1))
toggleMasterPane :: X ()
toggleMasterPane = do
flag <- XS.get
XS.modify(MasterPaneFlag . not . getFlag)
pickIncrFun (getFlag flag)
.....
.....
--- Add a key binding that calls toggleMasterPane, for me that looks like
this
, ("M-v", toggleMasterPane)
I find the ExtensibleState module allows you to do all sorts of tricks.
- Chris Wills
On Wed, Oct 1, 2014 at 9:10 PM, Brandon Allbery
On Wed, Oct 1, 2014 at 7:03 PM, Devin Mullins
wrote: I think another option is to make a new instance of LayoutClass that is just like Tall except for also supporting this message. In fact, you should be able to delegate to Tall for most definitions. Just writing off the cuff - could be wrong.
Delegating to Tall won't work; you'd have to copy the definition and modify it, like I suggested for (|||).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad

On Wed, Oct 1, 2014 at 10:55 PM, Christian Wills
instance ExtensionClass MasterPaneFlag where initialValue = MasterPaneFlag False
pickIncrFun :: Bool -> X () pickIncrFun flag = if flag then (sendMessage (IncMasterN (-1))) else (sendMessage (IncMasterN 1))
You might want to check the behavior of this around manual changes (mod-, and mod-.). It should at least be safe against mod-shift-space and manual setLayout, I think. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Wed, Oct 1, 2014 at 11:00 PM, Brandon Allbery
On Wed, Oct 1, 2014 at 10:55 PM, Christian Wills
wrote: instance ExtensionClass MasterPaneFlag where initialValue = MasterPaneFlag False
pickIncrFun :: Bool -> X () pickIncrFun flag = if flag then (sendMessage (IncMasterN (-1))) else (sendMessage (IncMasterN 1))
You might want to check the behavior of this around manual changes (mod-, and mod-.). It should at least be safe against mod-shift-space and manual setLayout, I think.
Right. If you change the master count manually with mod-, and mod-. this will toggle +/- 1 from your manually set master count depending on what the state was when you changed the master count manually. I don't find that to be totally off the wall given the spirit of not wanting to have to use mod-, and mod-. You could always IncMasterN(-100000) to bring it back to zero and then add 1 or leave it alone depending on the flag setting if you really wanted to.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Wed, Oct 1, 2014 at 11:10 PM, Christian Wills
You could always IncMasterN(-100000) to bring it back to zero and then add 1 or leave it alone depending on the flag setting if you really wanted to
Or mod-shift-space to bring it back into sync. Probably best to just replace those two bindings with something innocuous like (return ()) --- or maybe bind both of them to toggleMasterPane. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

mod-shift-space is even better (too bad EZconfigs broke it for me....will
have to look at that).
toggleMasterPane :: X ()
toggleMasterPane = do
flag <- XS.get
XS.modify(MasterPaneFlag . not . getFlag)
setLayout $ XMonad.layoutHook myConfig >> pickIncrFun (getFlag flag)
You can probably modify my code snippet as above (replacing myConfig with
whatever you actually called your xmonad config). Untested since setLayout
$ XMonad.layoutHook myConfig is broken for me....
On Wed, Oct 1, 2014 at 11:12 PM, Brandon Allbery
On Wed, Oct 1, 2014 at 11:10 PM, Christian Wills
wrote: You could always IncMasterN(-100000) to bring it back to zero and then add 1 or leave it alone depending on the flag setting if you really wanted to
Or mod-shift-space to bring it back into sync. Probably best to just replace those two bindings with something innocuous like (return ()) --- or maybe bind both of them to toggleMasterPane.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Thu, Oct 2, 2014 at 12:24 AM, Christian Wills
setLayout $ XMonad.layoutHook myConfig >> pickIncrFun (getFlag flag)
The precedence of ($) compared to (>>) is breaking you here. Use parentheses instead. Additionally, you are working in the X monad so you can get the actual layout (also removing the need for parentheses or precedence-changing tricks like ($)). This should look something like: asks config >>= setLayout >> pickIncrFun (getFlag flag) (untested) An unconditional setLayout means that things like full-screen or multiple layouts selected with (|||) and mod-space will be forcibly reset by this binding. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Damn it, you tricked me into writing it:
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses
#-}
import Control.Arrow
import XMonad
import XMonad.StackSet
data Flippy a = Flippy (Tall a) deriving (Show, Read)
data Flip = Flip deriving Typeable
instance Message Flip
instance LayoutClass Flippy a where
runLayout (Workspace id (Flippy tall) ms) r =
fmap (second (fmap Flippy)) $ runLayout (Workspace id tall ms) r
handleMessage (Flippy tall) m =
case flip of
Just _ -> return $ doFlip (Flippy tall)
Nothing -> fmap (fmap Flippy) $ handleMessage tall m
where flip = fromMessage m :: Maybe Flip
doFlip (Flippy (Tall 1 delta frac)) = Just $ Flippy $ Tall 2
delta frac
doFlip (Flippy (Tall _ delta frac)) = Just $ Flippy $ Tall 1
delta frac
description _ = "Flippy"
No guarantee this works, but it compiles.
On Wed, Oct 1, 2014 at 6:10 PM, Brandon Allbery
On Wed, Oct 1, 2014 at 7:03 PM, Devin Mullins
wrote: I think another option is to make a new instance of LayoutClass that is just like Tall except for also supporting this message. In fact, you should be able to delegate to Tall for most definitions. Just writing off the cuff - could be wrong.
Delegating to Tall won't work; you'd have to copy the definition and modify it, like I suggested for (|||).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

That works. I didn't try it directly, but cleaned it up a little
Damn it, you tricked me into writing it:
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses
#-}
import Control.Arrow
import XMonad
import XMonad.StackSet
data Flippy a = Flippy (Tall a) deriving (Show, Read)
data Flip = Flip deriving Typeable
instance Message Flip
instance LayoutClass Flippy a where
runLayout (Workspace id (Flippy tall) ms) r =
fmap (second (fmap Flippy)) $ runLayout (Workspace id tall ms) r
handleMessage (Flippy tall) m =
case flip of
Just _ -> return $ doFlip (Flippy tall)
Nothing -> fmap (fmap Flippy) $ handleMessage tall m
where flip = fromMessage m :: Maybe Flip
doFlip (Flippy (Tall 1 delta frac)) = Just $ Flippy $ Tall 2
delta frac
doFlip (Flippy (Tall _ delta frac)) = Just $ Flippy $ Tall 1
delta frac
description _ = "Flippy"
No guarantee this works, but it compiles.
On Wed, Oct 1, 2014 at 6:10 PM, Brandon Allbery
On Wed, Oct 1, 2014 at 7:03 PM, Devin Mullins
wrote: I think another option is to make a new instance of LayoutClass that is just like Tall except for also supporting this message. In fact, you should be able to delegate to Tall for most definitions. Just writing off the cuff - could be wrong.
Delegating to Tall won't work; you'd have to copy the definition and modify it, like I suggested for (|||).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Thanks to all for the help. I've now got it done as a configuration using an extension of Tall. I added a note to the issue ( http://code.google.com/p/xmonad/issues/detail?id=577&q=message#makechanges) that it can be closed. Final question - is there a writeup somewhere on extending the builtin Layouts as Devin showed here?

I prefer Devin's solution to mine but just for completeness here is an
updated version of my method which works no matter how many master windows
have been manually added or removed with mod-, or mod-. by resetting the
layout (effectively setting the number of master windows to 1). Thanks to
Brandon for pointing out some silliness I was doing.
data MasterPaneFlag = MasterPaneFlag { getFlag :: Bool }
deriving (Show, Typeable)
instance ExtensionClass MasterPaneFlag where
initialValue = MasterPaneFlag False
pickIncrFun :: Bool -> X ()
pickIncrFun flag = if flag then (sendMessage (IncMasterN (1))) else
(sendMessage (IncMasterN 0))
toggleMasterPane :: X ()
toggleMasterPane = do
flag <- XS.get
XS.modify(MasterPaneFlag . not . getFlag)
asks config >>= \c -> setLayout (XMonad.layoutHook c) >> pickIncrFun
(getFlag flag)
On Thu, Oct 2, 2014 at 3:57 PM, Mike Meyer
Thanks to all for the help. I've now got it done as a configuration using an extension of Tall. I added a note to the issue ( http://code.google.com/p/xmonad/issues/detail?id=577&q=message#makechanges) that it can be closed.
Final question - is there a writeup somewhere on extending the builtin Layouts as Devin showed here?
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad

Couple of docs on developing contribs:
http://www.haskell.org/haskellwiki/Xmonad/xmonad_development_tutorial
http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Doc-Developing.html
but the section on LayoutClass just says "to do"...
The API docs for LayoutClass are decent, though:
http://xmonad.org/xmonad-docs/xmonad/XMonad-Core.html#t:LayoutClass
Nothing on extending the built-in layouts. Building a data wrapper just
seemed like the the obvious thing to do.
On Thu, Oct 2, 2014 at 12:57 PM, Mike Meyer
Thanks to all for the help. I've now got it done as a configuration using an extension of Tall. I added a note to the issue ( http://code.google.com/p/xmonad/issues/detail?id=577&q=message#makechanges) that it can be closed.
Final question - is there a writeup somewhere on extending the builtin Layouts as Devin showed here?

I started with those docs and wrote up a blog entry documenting how to
extend a Layout. I haven't published it yet, and would appreciate feedback
on it. Also, if someone who can edit the wiki wants to use this to fill in
the appropriate part of the wiki docs, that would be fine by me.
You can get to the markdown on draftin at
https://draftin.com/documents/490906?token=i8AJR0nv8RK3G8KYV07NXxzArVeDgkTBv...
That should let you edit the markdown and show me the diffs. If you don't
want to deal with draftin, let me know and I'll see about getting it to you
another way.
Thanks,
Mike
On Oct 3, 2014 11:34 AM, "Devin Mullins"
Couple of docs on developing contribs: http://www.haskell.org/haskellwiki/Xmonad/xmonad_development_tutorial http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Doc-Developing.html but the section on LayoutClass just says "to do"...
The API docs for LayoutClass are decent, though: http://xmonad.org/xmonad-docs/xmonad/XMonad-Core.html#t:LayoutClass
Nothing on extending the built-in layouts. Building a data wrapper just
seemed like the the obvious thing to do.
On Thu, Oct 2, 2014 at 12:57 PM, Mike Meyer
wrote: Thanks to all for the help. I've now got it done as a configuration
using an extension of Tall. I added a note to the issue ( http://code.google.com/p/xmonad/issues/detail?id=577&q=message#makechanges) that it can be closed.
Final question - is there a writeup somewhere on extending the builtin
Layouts as Devin showed here?
participants (4)
-
Brandon Allbery
-
Christian Wills
-
Devin Mullins
-
Mike Meyer