Add SimpleFloat a very basic floating layout that will place windows according to their size hints

This commit is contained in:
Andrea Rossato 2008-01-26 20:54:10 +00:00
parent c84a26022d
commit de40bee12f
3 changed files with 79 additions and 5 deletions

View File

@ -22,7 +22,7 @@ module XMonad.Layout.Decoration
, DecorationStyle (..)
, DeConfig (..), defaultDeConfig, mkDefaultDeConfig
, shrinkText, CustomShrink ( CustomShrink )
, Shrinker (..)
, Shrinker (..), DefaultShrinker
, module XMonad.Layout.LayoutModifier
, fi
) where
@ -32,17 +32,14 @@ import Data.List
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Hooks.UrgencyHook
import XMonad.Layout.LayoutModifier
import XMonad.Layout.WindowArranger
import XMonad.Util.NamedWindows
import XMonad.Util.Invisible
import XMonad.Util.XUtils
import XMonad.Util.Font
import XMonad.Hooks.UrgencyHook
-- $usage
-- For usage examples you can see "XMonad.Layout.SimpleDecoration",
-- "XMonad.Layout.Tabbed", "XMonad.Layout.DwmStyle",

View File

@ -0,0 +1,76 @@
{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.SimpleFloat
-- Copyright : (c) 2007 Andrea Rossato
-- License : BSD-style (see xmonad/LICENSE)
--
-- Maintainer : andrea.rossato@unibz.it
-- Stability : unstable
-- Portability : unportable
--
-- A very simple layout. The simplest, afaik.
-----------------------------------------------------------------------------
module XMonad.Layout.SimpleFloat
( -- * Usage:
-- $usage
simpleFloat
, simpleFloat'
, SimpleDecoration (..), defaultSFConfig
, shrinkText, CustomShrink(CustomShrink)
, Shrinker(..)
) where
import XMonad
import qualified XMonad.StackSet as S
import XMonad.Layout.Decoration
import XMonad.Layout.SimpleDecoration
import XMonad.Layout.WindowArranger
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.SimpleFloat
--
-- Then edit your @layoutHook@ by adding the SimpleFloat layout:
--
-- > myLayouts = simpleFloat ||| Full ||| etc..
-- > main = xmonad defaultConfig { layoutHook = myLayouts }
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
-- | FIXME
simpleFloat :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout WindowArranger SimpleFloat) a
simpleFloat = decoration shrinkText defaultSFConfig (windowArranger $ SF 20)
-- | FIXME
simpleFloat' :: Shrinker s => s -> DeConfig SimpleDecoration a ->
ModifiedLayout (Decoration SimpleDecoration s)
(ModifiedLayout WindowArranger SimpleFloat) a
simpleFloat' s c = decoration s c (windowArranger $ SF (decoHeight c))
defaultSFConfig :: DeConfig SimpleDecoration a
defaultSFConfig = mkDefaultDeConfig $ Simple False
data SimpleFloat a = SF Dimension deriving (Show, Read)
instance LayoutClass SimpleFloat Window where
doLayout (SF i) sc (S.Stack w l r) = do wrs <- mapM (getSize i sc) (w : reverse l ++ r)
return (wrs, Nothing)
description _ = "SimpleFloat"
getSize :: Dimension -> Rectangle -> Window -> X (Window,Rectangle)
getSize i (Rectangle rx ry _ _) w = do
d <- asks display
bw <- asks (borderWidth . config)
wa <- io $ getWindowAttributes d w
let ny = ry + fi i
x = max rx $ fi $ wa_x wa
y = max ny $ 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)

View File

@ -120,6 +120,7 @@ library
XMonad.Layout.Roledex
XMonad.Layout.Simplest
XMonad.Layout.SimpleDecoration
XMonad.Layout.SimpleFloat
XMonad.Layout.Spiral
XMonad.Layout.Square
XMonad.Layout.ShowWName