aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/SimpleFloat.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-01-26 21:54:10 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-01-26 21:54:10 +0100
commit3323ce9eec52292ca88bf0654e79dec4f59e19af (patch)
tree9f8aaeda48345f0376f2c67637c84315572747ff /XMonad/Layout/SimpleFloat.hs
parentc20d5ea2c6f4446dceff581943e6cff0f8eb77f1 (diff)
downloadXMonadContrib-3323ce9eec52292ca88bf0654e79dec4f59e19af.tar.gz
XMonadContrib-3323ce9eec52292ca88bf0654e79dec4f59e19af.tar.xz
XMonadContrib-3323ce9eec52292ca88bf0654e79dec4f59e19af.zip
Add SimpleFloat a very basic floating layout that will place windows according to their size hints
darcs-hash:20080126205410-32816-5cbea7a3f698b6e53b6fd9986c4edef7a1d5992e.gz
Diffstat (limited to 'XMonad/Layout/SimpleFloat.hs')
-rw-r--r--XMonad/Layout/SimpleFloat.hs76
1 files changed, 76 insertions, 0 deletions
diff --git a/XMonad/Layout/SimpleFloat.hs b/XMonad/Layout/SimpleFloat.hs
new file mode 100644
index 0000000..6e7df92
--- /dev/null
+++ b/XMonad/Layout/SimpleFloat.hs
@@ -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)