
* On Thursday, January 20 2011, Alistair Gee wrote:
I have 4 monitors, but I am limited two 2 X screens due to my 2 nvidia cards. My current screen setup is:
+------------+------------+ | X screen 0 | X screen 1 | | monitor 1 | monitor 3 | +------------+------------+ | X screen 0 | X screen 1 | | monitor 2 | monitor 4 | +------------+------------+
That is, the nvidia driver combines monitor 1 and monitor 2 into the 1st X screen and monitor 3 and monitor 4 into a 2nd X screen.
To recreate the effect of 4 separate X screens, I use XMonad.Layout.LayoutScreens to create a 2x2 screen setup. The command I have in xmonad.hs is
layoutScreens 4 Grid
This works well. However, I would like to rearrange my screen setup to be instead as follows:
+------------+ | | | | +------------+------------+------------+ | | | | | | | | +------------+------------+------------+
Using the nvidia configuration tool, I can create the above as:
+------------+ | X screen 0 | | | +------------+------------+------------+ | X screen 1 | X screen 0 | X screen 1 | | | | | +------------+------------+------------+
or +------------+ | X screen 0 | | | +------------+------------+------------+ | X screen 1 | X screen 1 | X screen 0 | | | | | +------------+------------+------------+
However, once I do that, how do I use XMonad.Layout.LayoutScreens to create a 4 screen setup again, now that the positions of the monitors are different (and I can't use Grid to split up the layout)?
TIA
Hi Alistair, As you suggested, it's a question of writing an alternative layout. I can suggest: http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Layout-LayoutBuilder.htm... Otherwise it isn't difficult to directly specify the RectangleS more directly: {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} import XMonad import qualified XMonad.StackSet as W import XMonad.Util.Font import XMonad.StackSet -- use as layoutScreens (Tee 640 480) 4 data Tee a = Tee { tee_width, tee_height :: Dimension } deriving (Read,Show) instance (Read a, Show a) => LayoutClass Tee a where pureLayout (Tee w h) (Rectangle x0 y0 w0 h0) wins = let rects = [Rectangle x0 (y0+fi h) w h, Rectangle (x0 + fi w) y0 w h, Rectangle (x0 + fi w) (y0+fi h) w h, Rectangle (x0 + 2 * fi w) (y0+fi h) w h] in W.integrate wins `zip` rects I likely misunderstand whether xmonad sees separate screens (via xinerama): Above I assume xmonad gets a single screen, which suports the choice of (`layoutScreens` 4). Otherwise you probably have to adjust Adam