[xmonad] xinerama and per-screen automatic layout modification
adam vogt
vogt.adam at gmail.com
Thu Nov 20 17:50:52 UTC 2014
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
More information about the xmonad
mailing list