Difference between revisions of "Xmonad/Notable changes since 0.9"

From HaskellWiki
Jump to navigation Jump to search
(→‎Actions: Add a bunch of new xmc modules)
m (→‎Optional or obscure changes: clarify paintAndWrite formatting)
Line 50: Line 50:
 
* '''X.Hooks.DynamicLog urgency''' Urgency formatting now takes precedence over all other formatting, so xmobarStrip and dzenStrip are no longer needed. Multi-head users that distinguish urgent current from urgent visibles will need custom pretty printers but default behaviour is unchanged.
 
* '''X.Hooks.DynamicLog urgency''' Urgency formatting now takes precedence over all other formatting, so xmobarStrip and dzenStrip are no longer needed. Multi-head users that distinguish urgent current from urgent visibles will need custom pretty printers but default behaviour is unchanged.
   
* '''The X.Util.XUtils paintAndWrite utility's''' parameter types have changed to allow printing multiple strings. Configs using it will need to be updated to use [Align] and [String].
+
* '''The X.Util.XUtils''' <hask>paintAndWrite</hask> utility's parameter types have changed to allow printing multiple strings. Configs using it will need to be updated to use [Align] and [String].
   
 
== Changes to the xmonad core ==
 
== Changes to the xmonad core ==

Revision as of 20:57, 18 November 2011

This page is for keeping a record of significant changes in darcs xmonad and xmonad-contrib since the 0.9 releases. See 'darcs changes' for more details about miscellaneous feature enhancements, and documentation and bug fixes not noted here.

(0.9.1 was a maintenance release, with no changes to user functionality. 0.9.1 builds against haskell X11-1.5.0.0 while 0.9 requires 1.4.6.1. Otherwise the only changes are a few documentation updates, automatic detection of numlockMask, and a minor bug fix for forked processes.)

The idea is to put here a list of things which a user upgrading from 0.9 to the current darcs version might like to know, so that they are sure to be included in the next release change log.

Updates that require changes in xmonad.hs

numlockMask is now set automatically

Users explicitly setting numlockMask in their configs should remove those references. XConfig no longer has a numlockMask field.

If for some reason this detection isn't correct, you could still set it in the startupHook (or elsewhere), using this function:

setNumLockMask :: KeyMask -> X ()
setNumLockMask m = modify (\x -> x { numberlockMask = m })

Simplified interface for X.A.SpawnOn and X.H.DynamicHooks

Since contrib modules can now store custom state in XState, the additional IORef parameters are no longer required: Users have to remove the first parameter to the respective functions. The functions mkSpawner and initDynamicHooks are also no longer necessary and have been removed. The same applies to XMonad.Hooks.DynamicHooks. See below for examples.

MultiToggle

All instances of Transformer need to add another argument to k to provide a way to undo the modifier:

Old

instance Transformer StdTransformers Window where
    transform NBFULL       x k = k (noBorders Full)
    transform MIRROR       x k = k (Mirror x      )

New

instance Transformer StdTransformers Window where
    transform NBFULL       x k = k (noBorders Full) (\_ -> x)
    transform MIRROR       x k = k (Mirror x      ) (\(Mirror x') -> x')

X.A.GridSelect changes

gs_navigate changed incompatibly. There is no straightforward translation: just start over with your customization with reference to documentation in the module.

X.A.OnScreen changes

The type of onScreen has been changed to allow more general onScreen functions. The new onScreen takes any function that modifies the stack and runs it on the given screen. An onScreen' to run in X is also provided. Since XMonad can not guess what you'd like to do with the focus after running this function, onScreen also accepts a Focus data which tells XMonad how to act. See below for detailed examples. The more common "end user" functions like viewOnScreen and greedyViewOnScreen didn't change in their interface though.

Optional or obscure changes

Changes unlikely to affect most xmonad users.

  • X.Hooks.DynamicLog urgency Urgency formatting now takes precedence over all other formatting, so xmobarStrip and dzenStrip are no longer needed. Multi-head users that distinguish urgent current from urgent visibles will need custom pretty printers but default behaviour is unchanged.
  • The X.Util.XUtils paintAndWrite utility's parameter types have changed to allow printing multiple strings. Configs using it will need to be updated to use [Align] and [String].

Changes to the xmonad core

  • XState now supports state extensions in xmonad-contrib. See darcs source or documentation.
  • xmonad --verbose-version flag added to provide more detailed information about the xmonad build useful for troubleshooting.
  • xmonad --replace flag added to attempt to replace compliant window managers.
  • <+> is `mappend` for any Monoid now, not just ManageHook. Thus it can be used with keybindings, handleEventHook, X (a -> a), and more. Also (-->) works withing any Monad rather than being restricted to Query, and doF any Query(Endo a) rather than only Endo WindowSet.
  • The GenerateManpage script now uses the GPL'd pandoc to generate html and man versions of the manpage.
  • spawn works for non-ascii commands by assuming the user locale is utf8. Previously users would have had to use (spawn . Codec.Binary.UTF8.String.encodeString)

Changes to xmonad-contrib

Throughout xmonad-contrib many monadic computations have been generalized to work in any MonadIO, i.e. in X or directly in main in IO.

Updated modules

Actions

  • CycleWS now allows cycling within WSTagGroups while filtering out workspace IDs, e.g. from "tag2:baz" with `workspaces = ["tag1:foo","tag1:bar","tag2:foo","tag2:baz","tag2:yow" ]' only tag2's foo, baz, and yow workspaces would cycle. Toggling allows filtering out some workspaces such as "NSP".
  • DynamicWorkspaces includes several bug fixes and improvements.
  • GridSelect has a new interface and exports numerous new helpers. Most GridSelect users will need to modify xmonad.hs.
  • OnScreen has improved several functions and offers greater flexibility, however between 0.9 and 0.9.1 some interfaces changed. See changes in xmonad.hs for details.
  • PhysicalScreens added the exports onPrevNeighbour and onNextNeighbour.
  • Search has added new predefined searches.
  • TopicSpace between 0.9 and 0.9.1 TopicSpace added defaultTopicConfig for easier setup, manages its history via extensible state rather than U.StringProp, and in 0.9.1 it added reverseLastFocusedTopics.
  • WindowBringer can use a custom menu command in place of dmenu. (The old dmenu actions haven't changed.)
  • WindowMenu added the ability to use custom colors in its GridSelect menu.

Hooks

  • DynamicLog includes xmonadPropLog to output data via root window properties rather than via pipes. See also scripts/xmonadpropread.hs included with XMonadContrib source. For configs using X.H.UrgencyHook, enabling urgency on current or visible will override ppCurrent or ppVisible formatting and use the urgency formatting instead whenever a workspace contains urgent windows, similarly it ignores ppHidden formatting, eliminating the need for the dzen and xmobar format strippers.
  • ManageDocks avoidStruts has been extended to behave more sensibly with over under multi-head configurations, i.e. allowing the use of xmobar at the bottom of a screen positioned over another xinerama screen. Note that current wm specifications do not support per screen struts, although it is under discussion, so many applications won't set struts at an interior screen edge.
  • ManageHelpers has new currentWS query enabling per workspace differences in manageHooks.

Layout

  • BorderResize modifies layouts supporting the SetGeometry message to allow resizing windows by dragging their corners (without needing to press a modifier key). It is best used with X.L.PositionStoreFloat or the complete X.C.Bluetile, however it can also be used with X.L.WindowArranger.
  • Decoration has internal changes to support bluetile additions, including a new windowTitleAddons field in Theme.

Prompt

  • X.Prompt exports setInput and getInput for use in custom keymaps. copyString has been removed. The default quit bindings are Esc, C-[, and C-q. C-g is no longer bound.

Util

  • Dzen has many new helper functions useful for creating custom notifications or message popups.
  • XSelection putSelection has been removed. See Issue 317.
  • XUtils paintAndWrite now prints multiple strings, taking [Align] and [String] parameters in place of Align and String.

New contrib modules

Actions

  • BluetileCommands are the X.H.ServerMode commands used by the bluetile gtk2hs dock. Most of them can also be used with other interfaces to ServerMode if you have enabled the appropriate layout extensions from X.C.Bluetile.
  • DynamicWorkspaceGroups implements switching groups of workspaces all at once on all monitors. It uses a prompt interface to select, add, and delete groups. It also exports helpers to work with these actions directly.
  • DynamicWorkspaceOrder creates a custom ordering of workspaces for use with X.Actions.CycleWS.
  • GroupNavigation povides methods for cycling through groups of windows across workspaces, ignoring windows that do not belong to this group. A group consists windows matching a user-provided boolean query. It also enables jumping back to the last used window in a group, (an action of special interest to mod-Tab recent window users.)
  • KeyRemap allows remapping keymaps to, for example, switch between typing in Dvorak or US while keeping your xmonad keybindings in US layout
  • WorkspaceNames without changing the config workspace list, WorkspaceNames allows dynamic workspace renaming, translation from workspaceID to name for use in dynamic log, and swapping workspaces by name. It persists across restarts. See also X.Layout.WorkspaceDir.

Config

  • Bluetile enables the bluetile extensions minus the greeter and dock. See the bluetile project page for more details.

Hooks

  • CurrentWorkspaceOnTop logHook used to restack floating layouts, ensuring dragged windows stay on top, used by bluetile config.
  • PositionStoreHooks manageHook and eventHook to store and maintain position and size data, used by bluetile config.

Layout

  • ButtonDecoration provides window decoration with clickable menu, minimize, maximize, close buttons. Requires use of X.L.Minimize and X.L.Maximize and X.L.DecorationAddons.
  • DecorationAddons extra utilities to make decorations more useful.
  • DraggingVisualizer helper for X.L.WindowSwitcherDecoration to make dragged windows follow the mouse cursor.
  • MultiColumns Use as many columns as you'd like with as many windows in each column as you'd like.
  • PositionStoreFloat the main bluetile floating layout designed for dual-head, should be used along with X.L.NoFrillsDecoration and X.L.BorderResize. (Currently requires use of mouse to move and resize floating windows.)
  • WindowSwitcherDecoration drag windows on top of each other to swap positions. Can be used either with or without the ButtonDecoration action buttons.

Util

  • ExtensibleState allows storing custom mutable state in xmonad. Can optionally be made persistent over restarts.
  • PositionStore stores window position and size info in XState for better float management. Used extensively by X.C.Bluetile.
  • SpawnOnce spawns a command once and only once. Useful for session settings unique to xmonad to be run from startupHook only on login rather than on each xmonad restart.

Deleted modules

Related Projects

xmonad-light allows using a limited version of xmonad without having to have ghc installed. It provides a special syntax to customize a few common options using xmonad.conf instead of xmonad.hs.

xmonad-extras includes some modules with additional dependencies, like a Volume control, an MPD prompt and the xmonad-eval package that uses the hint interpreter to manipulate xmonad state during runtime via arbitrary haskell expressions ala emacs eval.

Bluetile is a tiling window manager based on xmonad which focuses on making the tiling paradigm easily accessible to users coming from traditional window managers by drawing on known conventions. It provides both keyboard and mouse access for its features. It is designed to be usable "out of the box" without being configurable, however all its core features excluding its dock are provided by xmonad-contrib extensions. People wanting a customized bluetile-like window manager can use XMonad.Config.Bluetile as a base or cherry pick modules providing the features they need.

yeganesh is a wrapper for dmenu that offers more commonly used choices first in the menu. Here is [example] of using yeganesh and dmenu with xmonad.

xmenud is a hierarchical pop-up gtk menu written in python, useful to spawn from a key binding. (Available in archlinux's AUR or via git from the website.

dzen-utils provides combinators for creating and processing dzen2 input strings.

hlint parses haskell source and offers suggestions on how to improve it. (Requires >=ghc-6.10)

gnome socket applet allows displaying xmonad logHook output in gnome-panel via a localhost port.

xmonad log applet allows displaying xmonad logHook output in gnome-panel via dbus.

xmonad log plasmoid enables logHook output to kde plasmoids, also via dbus. (See also charon's version at git://git.thomasrast.ch/xmonad-log-plasmoid.git .)

taffybar is a gtk2hs based desktop information bar including an integrated system tray. It also communicates via dbus. It is similar to xmobar, but gives up some simplicity for flexibility plus a reasonable helping of eye candy.

Detailed examples regarding changes to xmonad.hs

XState change details

Since contrib modules can now store custom state in XState, the SpawnOn and DynamicHooks IORef parameters are no longer required: Users have to remove the first parameter to the respective functions. The functions mkSpawner and initDynamicHooks are also no longer necessary and have been removed.

Example:

-- Old code:
 sp <- mkSpawner
 ..
  [((mod1Mask,xK_k), shellPromptHere sp defaultXPConfig
   ..]

The above has to be changed to:

  -- no mkSpawner line
  ..
  [((mod1Mask,xK_k), shellPromptHere defaultXPConfig)
   ..]

The same applies to XMonad.Hooks.DynamicHooks.

OnScreen change details

The type of onScreen has been changed to allow more general onScreen functions. The old onScreen was very limited. Basicly the only working function derived from onScreen was viewOnScreen, since the greedyViewOnScreen never worked as supposed to, and any other function wouldn't work either.

The new onScreen takes any function that modifies the stack and runs it on the given screen. Since XMonad can not guess what you'd like to do with the focus after running this function, onScreen also accepts a Focus data which tells XMonad how to act.

Comparison:

---- Old version ----

-- Old type of onScreen:
onScreen :: (WorkspaceId -> WindowSet -> WindowSet) -- ^ default action
         -> ScreenId                                -- ^ screen id
         -> WorkspaceId                             -- ^ index of the workspace
         -> WindowSet                               -- ^ current stack
         -> WindowSet

-- The old implementation of viewOnScreen was:
viewOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
viewOnScreen sc i = onScreen view sc i


---- New version ----

-- The new Focus data:
data Focus = FocusNew                       -- ^ always focus the new screen
           | FocusCurrent                   -- ^ always keep the focus on the current screen
           | FocusTag WorkspaceId           -- ^ always focus tag i on the new stack
           | FocusTagVisible WorkspaceId    -- ^ focus tag i only if workspace with tag i is visible on the old stack

-- New type of onScreen:
onScreen :: (WindowSet -> WindowSet) -- ^ function to run
         -> Focus                    -- ^ what to do with the focus
         -> ScreenId                 -- ^ screen id
         -> WindowSet                -- ^ current stack
         -> WindowSet

-- A few example implementations (don't worry - they're already built in):
viewOnScreen           :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
viewOnScreen sc i       = onScreen (view i) (FocusTag i) sc
greedyViewOnScreen     :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
greedyViewOnScreen sc i = onScreen (greedyView i) FocusCurrent sc