diff options
author | joamaki <joamaki@gmail.com> | 2008-04-25 00:09:57 +0200 |
---|---|---|
committer | joamaki <joamaki@gmail.com> | 2008-04-25 00:09:57 +0200 |
commit | 8ee7b23dc23a0daab428619833992f11af3c2c0b (patch) | |
tree | fc63783758c61b46b50c43b6ebd26fd3d514836c /XMonad/Layout | |
parent | 74a8c5ede5dbe7752cbb108e1659ca8800ed8921 (diff) | |
download | XMonadContrib-8ee7b23dc23a0daab428619833992f11af3c2c0b.tar.gz XMonadContrib-8ee7b23dc23a0daab428619833992f11af3c2c0b.tar.xz XMonadContrib-8ee7b23dc23a0daab428619833992f11af3c2c0b.zip |
new contrib layout: XMonad.Layout.SimplestFloat - A floating layout like SimpleFloat, but without decoration
darcs-hash:20080424220957-2bec7-8dfa615dfd80ffeee4a464ea2713074938d768d0.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r-- | XMonad/Layout/SimplestFloat.hs | 64 |
1 files changed, 64 insertions, 0 deletions
diff --git a/XMonad/Layout/SimplestFloat.hs b/XMonad/Layout/SimplestFloat.hs new file mode 100644 index 0000000..61a3c0d --- /dev/null +++ b/XMonad/Layout/SimplestFloat.hs @@ -0,0 +1,64 @@ +{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-} +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Layout.SimplestFloat +-- Copyright : (c) 2008 Jussi Mäki +-- License : BSD-style (see xmonad/LICENSE) +-- +-- Maintainer : joamaki@gmail.com +-- Stability : unstable +-- Portability : unportable +-- +-- A basic floating layout like SimpleFloat but without the decoration. +----------------------------------------------------------------------------- + +module XMonad.Layout.SimplestFloat + ( -- * Usage: + -- $usage + simplestFloat + , SimplestFloat + ) where + +import XMonad +import qualified XMonad.StackSet as S +import XMonad.Layout.WindowArranger +import XMonad.Layout.LayoutModifier + +-- $usage +-- You can use this module with the following in your +-- @~\/.xmonad\/xmonad.hs@: +-- +-- > import XMonad.Layout.SimplestFloat +-- +-- Then edit your @layoutHook@ by adding the SimplestFloat layout: +-- +-- > myLayouts = simplestFloat ||| Full ||| etc.. +-- > main = xmonad defaultConfig { layoutHook = myLayouts } +-- +-- For more detailed instructions on editing the layoutHook see: +-- +-- "XMonad.Doc.Extending#Editing_the_layout_hook" + +-- | A simple floating layout where every window is placed according +-- to the window's initial attributes. +simplestFloat :: Eq a => (ModifiedLayout WindowArranger SimplestFloat) a +simplestFloat = (windowArrangeAll $ SF) + +data SimplestFloat a = SF deriving (Show, Read) +instance LayoutClass SimplestFloat Window where + doLayout SF sc (S.Stack w l r) = do wrs <- mapM (getSize sc) (w : reverse l ++ r) + return (wrs, Nothing) + description _ = "SimplestFloat" + +getSize :: Rectangle -> Window -> X (Window,Rectangle) +getSize (Rectangle rx ry _ _) w = do + d <- asks display + bw <- asks (borderWidth . config) + wa <- io $ getWindowAttributes d w + let x = max rx $ fi $ wa_x wa + y = max ry $ fi $ wa_y wa + wh = (fi $ wa_width wa) + (bw * 2) + ht = (fi $ wa_height wa) + (bw * 2) + return (w, Rectangle x y wh ht) + where + fi x = fromIntegral x
\ No newline at end of file |