[xmonad] Call for xmonad.hs
Don Stewart
dons at galois.com
Fri Oct 31 20:59:02 EDT 2008
gwern0:
> Followup: OK, so as everyone can see, I've gone through the config
> archive and checked everything in GHCi.
>
> I've moved everything that didn't compile into
> <http://haskell.org/haskellwiki/Xmonad/Config_archive#Old_configurations>.
> This isn't a subpage, but a subsection. (Of course, with things split
> out like that, it certainly would be easy to make it a subpage if
> desired.)
>
> In total, there were 20 configurations that worked. Including 1 I was
> sent privately, that makes 21 to work with. There were many which
> didn't work; some for odd reasons. Sereven's failed because some sort
> of prompt theme was defined but not used; 2 failed because a constant
> inadvertently had come to clash with a function (I fixed those); and a
> good 4 or 5 broke because of the defaultGaps move and related changes.
Good work!
> Later I'll take a look at them and see what commonalities I see.
> Offhand, 'cat *|sort|uniq -c|sort' turns out some surprising results:
>
> 3 import Data.Ratio ((%))
> 3 import Graphics.X11
> 3 import XMonad.Actions.SwapWorkspaces
> 3 import XMonad.Hooks.SetWMName
> 3 import XMonad.Layout.Gaps
> 3 import XMonad.Layout.WindowNavigation
> 3 import XMonad.Operations
> 3 main = xmonad $ defaultConfig
> 3 myManageHook = composeAll
> 4 import qualified Data.Map as M
> 4 import System.IO (hPutStrLn)
> 4 import XMonad.Actions.UpdatePointer
> 4 import XMonad.Hooks.EwmhDesktops
> 4 import XMonad.Util.Run
> 4 import XMonad.Util.Run (spawnPipe)
> 5 import Data.Bits ((.|.))
> 5 import Data.Ratio
> 5 import XMonad.Actions.Submap
> 5 import XMonad.Layout
> 5 import XMonad.Layout.TwoPane
> 6 import System.Exit
> 6 import XMonad.Actions.CycleWS
> 6 import XMonad.Actions.DwmPromote
> 6 import XMonad.Layout.Tabbed
> 7 import System.IO
> 7 import XMonad.Hooks.UrgencyHook
> 7 import XMonad.Prompt.Shell
> 7 import XMonad.Prompt.Ssh
> 8 import XMonad.Hooks.DynamicLog
> 8 import XMonad.Util.EZConfig
> 9 import XMonad.Layout.NoBorders
>
> Looks to me perhaps the calls to make NoBorders a default are
> sensible. Also, 16 of the 21 configs use Data.Map in some capacity,
> which is interesting.
*VERY* interesting data. And great vision to think of this Gwern!
Might be time to revisit the defaults. Especially if we can gather more
configs.
-- Don
More information about the xmonad
mailing list