aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
authorJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-11-15 19:48:33 +0100
committerJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-11-15 19:48:33 +0100
commita64225bbe26df7d9873ac1d4c8143e3146045b7a (patch)
tree03ca9312a6fa32bd143562645d6373b8c75e88f2 /XMonad/Layout
parent77bfd730a1a6f970a22c4c06cce0506101470ffd (diff)
downloadXMonadContrib-a64225bbe26df7d9873ac1d4c8143e3146045b7a.tar.gz
XMonadContrib-a64225bbe26df7d9873ac1d4c8143e3146045b7a.tar.xz
XMonadContrib-a64225bbe26df7d9873ac1d4c8143e3146045b7a.zip
PositionStoreFloat - a floating layout with support hooks
Ignore-this: 8b1d0fcef1465356d72cb5f1f32413b6 darcs-hash:20091115184833-594c5-9534e1ec9be959d18713bfdd1edbc1f5995cc4a8.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r--XMonad/Layout/BorderResize.hs6
-rw-r--r--XMonad/Layout/PositionStoreFloat.hs92
2 files changed, 96 insertions, 2 deletions
diff --git a/XMonad/Layout/BorderResize.hs b/XMonad/Layout/BorderResize.hs
index 56b6425..b1fc083 100644
--- a/XMonad/Layout/BorderResize.hs
+++ b/XMonad/Layout/BorderResize.hs
@@ -12,8 +12,10 @@
-- This layout modifier will allow to resize windows by dragging their
-- borders with the mouse. However, it only works in layouts or modified
-- layouts that react to the 'SetGeometry' message.
--- "XMonad.Layout.WindowArranger" can be used to create such a setup.
--- BorderResize is probably most useful in floating layouts.
+-- "XMonad.Layout.WindowArranger" can be used to create such a setup,
+-- but it is probably must useful in a floating layout such as
+-- "XMonad.Layout.PositionStoreFloat" with which it has been mainly tested.
+-- See the documentation of PositionStoreFloat for a typical usage example.
--
-----------------------------------------------------------------------------
diff --git a/XMonad/Layout/PositionStoreFloat.hs b/XMonad/Layout/PositionStoreFloat.hs
new file mode 100644
index 0000000..4797932
--- /dev/null
+++ b/XMonad/Layout/PositionStoreFloat.hs
@@ -0,0 +1,92 @@
+{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, PatternGuards #-}
+----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.PositionStoreFloat
+-- Copyright : (c) Jan Vornberger 2009
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : jan.vornberger@informatik.uni-oldenburg.de
+-- Stability : unstable
+-- Portability : not portable
+--
+-- A floating layout which has been designed with a dual-head setup
+-- in mind. It makes use of "XMonad.Util.PositionStore" as well as
+-- "XMonad.Hooks.PositionStoreHooks" . Since there is currently no way
+-- to move or resize windows with the keyboard alone in this layout,
+-- it is adviced to use it in combination with a decoration such as
+-- "XMonad.Layout.NoFrillsDecoration" (to move windows) and the
+-- layout modifier "XMonad.Layout.BorderResize" (to resize windows).
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.PositionStoreFloat
+ ( -- * Usage
+ -- $usage
+ positionStoreFloat
+ ) where
+
+import XMonad
+import XMonad.Util.PositionStore
+import qualified XMonad.StackSet as S
+import XMonad.Layout.WindowArranger
+import Control.Monad(when)
+import Data.Maybe(isJust)
+import Data.List(nub)
+
+-- $usage
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.PositionStoreFloat
+-- > import XMonad.Layout.NoFrillsDecoration
+-- > import XMonad.Layout.BorderResize
+--
+-- Then edit your @layoutHook@ by adding the PositionStoreFloat layout.
+-- Below is a suggestion which uses the mentioned NoFrillsDecoration and
+-- BorderResize:
+--
+-- > myLayouts = floatingDeco $ borderResize $ positionStoreFloat ||| etc..
+-- > where floatingDeco l = noFrillsDeco shrinkText defaultTheme l
+-- > main = xmonad defaultConfig { layoutHook = myLayouts }
+--
+-- See the documentation of "XMonad.Hooks.PositionStoreHooks" on how
+-- to add the support hooks.
+
+positionStoreFloat :: PositionStoreFloat a
+positionStoreFloat = PSF (Nothing, [])
+
+data PositionStoreFloat a = PSF (Maybe Rectangle, [a]) deriving (Show, Read)
+instance LayoutClass PositionStoreFloat Window where
+ description _ = "PSF"
+ doLayout (PSF (maybeChange, paintOrder)) sr (S.Stack w l r) = do
+ posStore <- getPosStore
+ let wrs = map (\w' -> (w', pSQ posStore w' sr)) (reverse l ++ r)
+ let focused = case maybeChange of
+ Nothing -> (w, pSQ posStore w sr)
+ Just changedRect -> (w, changedRect)
+ let wrs' = focused : wrs
+ let paintOrder' = nub (w : paintOrder)
+ when (isJust maybeChange) $ do
+ updatePositionStore focused sr
+ return (reorder wrs' paintOrder', Just $ PSF (Nothing, paintOrder'))
+ where
+ pSQ posStore w' sr' = case (posStoreQuery posStore w' sr') of
+ Just rect -> rect
+ Nothing -> (Rectangle 50 50 200 200) -- should usually not happen
+ pureMessage (PSF (_, paintOrder)) m
+ | Just (SetGeometry rect) <- fromMessage m =
+ Just $ PSF (Just rect, paintOrder)
+ | otherwise = Nothing
+
+updatePositionStore :: (Window, Rectangle) -> Rectangle -> X ()
+updatePositionStore (w, rect) sr = modifyPosStore (\ps ->
+ posStoreInsert ps w rect sr)
+
+reorder :: (Eq a) => [(a, b)] -> [a] -> [(a, b)]
+reorder wrs order =
+ let ordered = concat $ map (pickElem wrs) order
+ rest = filter (\(w, _) -> not (w `elem` order)) wrs
+ in ordered ++ rest
+ where
+ pickElem list e = case (lookup e list) of
+ Just result -> [(e, result)]
+ Nothing -> []