From 4866f2e367dfcf22a9591231ba40948826a1b438 Mon Sep 17 00:00:00 2001 From: Spencer Janssen Date: Thu, 1 Nov 2007 21:10:59 +0100 Subject: Hierarchify darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz --- XMonad/Layout/MagicFocus.hs | 51 +++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 51 insertions(+) create mode 100644 XMonad/Layout/MagicFocus.hs (limited to 'XMonad/Layout/MagicFocus.hs') diff --git a/XMonad/Layout/MagicFocus.hs b/XMonad/Layout/MagicFocus.hs new file mode 100644 index 0000000..57e5b7a --- /dev/null +++ b/XMonad/Layout/MagicFocus.hs @@ -0,0 +1,51 @@ +{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-} + +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Layout.MagicFocus +-- Copyright : (c) Peter De Wachter +-- License : BSD +-- +-- Maintainer : Peter De Wachter +-- Stability : unstable +-- Portability : unportable +-- +-- Automagically put the focused window in the master area. +----------------------------------------------------------------------------- + +module XMonad.Layout.MagicFocus + (-- * Usage + -- $usage + MagicFocus(MagicFocus) + ) where + +import Graphics.X11.Xlib +import XMonad +import XMonad.StackSet + +-- $usage +-- > import XMonad.Layout.MagicFocus +-- > layouts = [ Layout $ MagicFocus tiled , Layout $ MagicFocus $ Mirror tiled ] + +-- %import XMonad.Layout.MagicFocus +-- %layout , Layout $ MagicFocus tiled +-- %layout , Layout $ MagicFocus $ Mirror tiled + + +data MagicFocus l a = MagicFocus (l a) deriving ( Show , Read ) + +instance (LayoutClass l Window) => LayoutClass (MagicFocus l) Window where + doLayout = magicFocus + +magicFocus :: LayoutClass l Window => MagicFocus l Window -> Rectangle + -> Stack Window -> X ([(Window, Rectangle)], Maybe (MagicFocus l Window)) +magicFocus (MagicFocus l) r s = + withWindowSet $ \wset -> do + (ws,nl) <- doLayout l r (swap s $ peek wset) + case nl of + Nothing -> return (ws, Nothing) + Just l' -> return (ws, Just $ MagicFocus l') + +swap :: (Eq a) => Stack a -> Maybe a -> Stack a +swap (Stack f u d) focused | Just f == focused = Stack f [] (reverse u ++ d) + | otherwise = Stack f u d -- cgit v1.2.3