aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/SimpleFloat.hs
blob: 89c3cab8269a6b7d0dab2de7e8d246050c857e31 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
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 (windowArrangeAll $ SF 20)

-- | FIXME
simpleFloat' :: Shrinker s => s -> DeConfig SimpleDecoration a -> 
               ModifiedLayout (Decoration SimpleDecoration s)
	      (ModifiedLayout WindowArranger SimpleFloat) a
simpleFloat' s c = decoration s c (windowArrangeAll $ 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)