[xmonad] Patch: Floating layout like SimpleFloat, but without the decorations

Jussi Maki joamaki at gmail.com
Thu Apr 24 18:22:46 EDT 2008


Hi, 

Here's a modified SimpleFloat without the decorations that kept
bugging me.
                                                                                                                    
I also dropped the mouse resize support since moving the windows has
to be done through mouse bindings that by default push the window to
the floating mode which doesn't support the mouse resize anyway. Maybe
a different set of bindings that don't set the window to the floating
mode when the workspace is in one of the floating layouts might be a
better option.
                                                                                                                              
Fri Apr 25 01:09:57 EEST 2008 joamaki at gmail.com
  * new contrib layout: XMonad.Layout.SimplestFloat - A floating
    layout like SimpleFloat, but without decoration
-------------- next part --------------

New patches:

[new contrib layout: XMonad.Layout.SimplestFloat - A floating layout like SimpleFloat, but without decoration
joamaki at gmail.com**20080424220957] {
addfile ./XMonad/Layout/SimplestFloat.hs
hunk ./XMonad/Layout/SimplestFloat.hs 1
-
+{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.SimplestFloat
+-- Copyright   :  (c) 2008 Jussi Mäki
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  joamaki at 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
hunk ./xmonad-contrib.cabal 159
+                        XMonad.Layout.SimplestFloat
}

Context:

[Error fix for Tabbed when tabbar always shown
Ivan.Miljenovic at gmail.com**20080424063135] 
[remove my config file -- the wiki is where its at.
Don Stewart <dons at galois.com>**20080419195650] 
[tweaks to docs for SimpleDecoration
Don Stewart <dons at galois.com>**20080418215155] 
[Allow tabbar to always be shown.
Ivan.Miljenovic at gmail.com**20080415043728
 Patch take 4, hopefully the final version.  Includes droundy's suggestions.
] 
[polish
Don Stewart <dons at galois.com>**20080418033133] 
[Script-based hooks
Trevor Elliott <trevor at galois.com>**20080416213024] 
[Don't strictify the Display component, this triggers a bug in GHC 6.6
Spencer Janssen <sjanssen at cse.unl.edu>**20080416185733] 
[Fix to IM modifier.
Roman Cheplyaka <roma at ro-che.info>**20080414232437
 Avoid differentiating integrated stack by using StackSet.filter.
] 
[IM layout converted to LayoutModifier, which can be applied to any layout
Ivan N. Veselov <veselov at gmail.com>**20080413205824] 
[stictify some fields
Don Stewart <dons at galois.com>**20080413070117] 
[strictify some fields
Don Stewart <dons at galois.com>**20080413065958] 
[Fix window order in EWMH
Joachim Breitner <mail at joachim-breitner.de>**20080411134411
 For pagers to draw the stacking order correctly, the focused window has to
 be the last in the list. Thus put an appropriate implementation of allWindows
 into the Module.
 This does not work perfectly with floating windows.
] 
[remove myself as maintainer of CopyWindow.
David Roundy <droundy at darcs.net>**20080409144333
 I'm not sure who's maintaining this, but it's not me.
] 
[XMonad.Util.WindowProperties: add WM_WINDOW_ROLE as Role
Roman Cheplyaka <roma at ro-che.info>**20080409174935] 
[Generalize copyWindow, minor style change
Spencer Janssen <sjanssen at cse.unl.edu>**20080408210050] 
[XMonad.Actions.CopyWindow: added copyToAll and killAllOtherCopies functions
Ivan N. Veselov <veselov at gmail.com>**20080408195111] 
[XMonad.Actions.UpdatePointer: doc fix
Lukas Mai <l.mai at web.de>**20080407152741] 
[XMonad.Util.Font: minor reformatting
Lukas Mai <l.mai at web.de>**20080406020935] 
[DynamicLog: resolve merge conflict
Lukas Mai <l.mai at web.de>**20080406020527] 
[Encode the entire DynamicLog output, instead of just window title.
lithis <xmonad at selg.hethrael.org>**20080329031537] 
[DynamicLog: add support for UTF-8 locales when compiled with XFT or UFT-8 support
Andrea Rossato <andrea.rossato at unibz.it>**20080313102643] 
[XMonad.Util.Font: don't call setlocale; core does it for us
Lukas Mai <l.mai at web.de>**20080406013123] 
[XMonad.Util.NamedWindows: fix imports
Lukas Mai <l.mai at web.de>**20080326172745] 
[Changed getName to use locale-aware functions
Mats Jansborg <mats at jansb.org>**20070819132104
 Rewrote getName using getTextProperty and wcTextPropertyToTextList.
] 
[Added next-window versions of the raise* functions.
Ian Zerny <ian at zerny.dk>**20080405182900] 
[XMonad.Layout.Master: initial import
Lukas Mai <l.mai at web.de>**20080404220734] 
[update contrib for applySizeHints changes
Lukas Mai <l.mai at web.de>**20080404220558] 
[XMonad.Hooks.ManageDocks: haddock fix
Lukas Mai <l.mai at web.de>**20080404220532] 
[MultiToggle/Instances: ghc 6.6 can't parse LANGUAGE pragma
Brent Yorgey <byorgey at gmail.com>**20080404200157] 
[Document _NET_ACTIVE_WINDOW behaviour more exactly
Joachim Breitner <mail at joachim-breitner.de>**20080404072944] 
[_NET_ACTIVE_WINDOW moves windows if necessary
Joachim Breitner <mail at joachim-breitner.de>*-20080402143811
 This makes EWMH behave a bit more like metacity: If _NET_ACTIVE_WINDOW is
 received and the window is not on the current worspace, it is brought here 
 (instead of the workspace switched to the other one). So for example, if you
 click on the pidgin icon in the panel and the buddy list is already open some
 where it is moved here.
] 
[onstart=lower, solves floating dzen issue
Don Stewart <dons at galois.com>**20080403203425] 
[some bang patterns
Don Stewart <dons at galois.com>**20080403172246] 
[have 'dzen' use autoStruts to detect the gaps
Don Stewart <dons at galois.com>**20080403003130] 
[Actions/Search.hs: add dictionary.com search
Brent Yorgey <byorgey at gmail.com>**20080402150521] 
[_NET_ACTIVE_WINDOW moves windows if necessary
Joachim Breitner <mail at joachim-breitner.de>**20080402143811
 This makes EWMH behave a bit more like metacity: If _NET_ACTIVE_WINDOW is
 received and the window is not on the current worspace, it is brought here 
 (instead of the workspace switched to the other one). So for example, if you
 click on the pidgin icon in the panel and the buddy list is already open some
 where it is moved here.
] 
[HintedGrid: guesstimate window flexibility and layout rigid windows first
Lukas Mai <l.mai at web.de>**20080402042846] 
[HintedGrid: try both bottom-up/top-down window placement to minimize unused space
Lukas Mai <l.mai at web.de>**20080402012538] 
[Grid/HintedGrid: use an ncolumns formula inspired by dwm's "optimal" mode
Lukas Mai <l.mai at web.de>**20080402012126] 
[XMonad.Layout.Gaps: new contrib module for manual gap support, in the few cases where ManageDocks is not appropriate (dock apps that don't set STRUTS properly, adjusting for a display that is cut off on one edge, etc.)
Brent Yorgey <byorgey at gmail.com>**20080402003742] 
[improve WindowGo.hs Haddock formatting
gwern0 at gmail.com**20080401023130] 
[forgot a haddock for getEditor in Shell.hs
gwern0 at gmail.com**20080401022012] 
[WindowGo.hs: +raiseBrowser, raiseEditor
gwern0 at gmail.com**20080401021740
 Specialize runOrRaise in the same way as with Actions.Search, for one's browser and one's editors.
] 
[RunOrRaise.hs: FF 3 doesn't use the "Firefox-bin" classname
gwern0 at gmail.com**20080401015049] 
[Search.hs: remove an argument from selectSearch and promptSearch
gwern0 at gmail.com**20080401013947
 The new getBrowser function allows us to mv the old selectSearch and promptSearch aside as too-general functions, and replace them with new versions, which employ getBrowser to supply one more argument. This allows us to replace the tedious 'selectSearch google "firefox"; selectSearch yahoo "firefox"...' with shorter 'selectSearch google' and so on. One less argument.
 
 Also, update the docs.
] 
[Shell.hs: +getBrowser, getEditor, helper function
gwern0 at gmail.com**20080401013447
 The helper function asks the shell for the value of a variable, else returns the second argument.
 getBrowser and getEditor obviously specialize it for two particular possibly queries
] 
[XMonad.Layout.HintedGrid: initial import
Lukas Mai <l.mai at web.de>**20080401231722] 
[Documentation improvement.
Roman Cheplyaka <roma at ro-che.info>**20080401134305] 
[Remove broken link to screenshot.
Roman Cheplyaka <roma at ro-che.info>**20080331210854] 
[MultiToggle: add new XMonad.Layout.MultiToggle.Instances module for common instances of Transformer, update MultiToggle docs accordingly
Brent Yorgey <byorgey at gmail.com>**20080331201739] 
[XMonad.Actions.CycleRecentWS: initial import
Michal Janeczek <janeczek at gmail.com>**20080331111906] 
[XMonad.Hooks.ManageDocks: export checkDoc
Lukas Mai <l.mai at web.de>**20080331012911] 
[XMonad.Layout.Grid: fix indentation
Lukas Mai <l.mai at web.de>**20080330004859] 
[move Direction type from WindowNavigation to ManageDocks (ManageDocks will move into the core, taking Direction with it)
Brent Yorgey <byorgey at gmail.com>**20080331010127] 
[ManageDocks: clean up + add more documentation
Brent Yorgey <byorgey at gmail.com>**20080331002929] 
[Util.Run, Hooks.DynamicLog: re-export hPutStrLn and hPutStr from Util.Run for convenience, and update DynamicLog documentation to show proper imports
Brent Yorgey <byorgey at gmail.com>**20080328205446] 
[ManageDocks: add avoidStrutsOn, for covering some docks and not others by default.
Brent Yorgey <byorgey at gmail.com>**20080327203940] 
[ManageDocks: add ability to toggle individual gaps independently
Brent Yorgey <byorgey at gmail.com>**20080327111722] 
[PerWorkspace: add modWorkspace(s) combinators, for selectively applying layout modifiers to certain workspaces but not others
Brent Yorgey <byorgey at gmail.com>**20080326214351] 
[Haddock fix
Roman Cheplyaka <roma at ro-che.info>**20080330134435] 
[Remove stale status gaps code
Spencer Janssen <sjanssen at cse.unl.edu>**20080329230737] 
[TAG 0.7
Spencer Janssen <sjanssen at cse.unl.edu>**20080329202416] 
Patch bundle hash:
def8ed03d5527a1bcb681e27234ee3fdd2bb93f0


More information about the xmonad mailing list