xinerama and per-screen automatic layout modification

Hi, I'm using xmonad with two equally-sized screens the left one of which I sometimes turn into pivot mode (rotate 90°) to read articles. Now 'Tall' isn't great on a portrait monitor, so I'm looking for a layout modifier that acts as follows: * If on the right monitor: No modification * If on the left monitor: o If in pivot mode, apply the Mirror layout modifier. o Otherwise, apply the Reflect layout modifier. (because I like my master windows in the center) Has anybody worked on something like this before? If not, I'd try to write a contrib module, probably re-using some code from Actions.PhysicalScreens. Any pointers / pitfalls to be expected? kthx. Best, Steffen

Hi Steffen, I think it is simpler to check if the screen has height > width, and then do what Mirror does if that happens to be the case. The following code is a slight modification of the code for Mirror probably does that (it compiles but I have not tested it): {-# LANGUAGE MultiParamTypeClasses #-} -- at the top of the file {-# LANGUAGE FlexibleInstances #-} import XMonad import Control.Arrow import qualified XMonad.StackSet as W -- | Mirror a layout, compute its 90 degree rotated form. newtype MirrorAspect l a = MirrorAspect (l a) deriving (Show, Read) instance LayoutClass l a => LayoutClass (MirrorAspect l) a where runLayout (W.Workspace i (MirrorAspect l) ms) r@(Rectangle _ _ w h) = (map (second mirrorRect) *** fmap MirrorAspect) `fmap` runLayout (W.Workspace i l ms) (mirrorRect r) where -- | possibly Mirror a rectangle mirrorRect :: Rectangle -> Rectangle mirrorRect r0@(Rectangle rx ry rw rh) | h > w = Rectangle ry rx rh rw | otherwise = r0 handleMessage (MirrorAspect l) = fmap (fmap MirrorAspect) . handleMessage l description (MirrorAspect l) = "MirrorAspect "++ description l Regards, Adam
participants (2)
-
adam vogt
-
Steffen Schuldenzucker