Oops, sorry for the dupe.

On Sat, Sep 27, 2014 at 1:08 AM, Devin Mullins <devin.mullins@gmail.com> wrote:
Norbert, as the original author of this, does this look okay to you? If you
don't mind/care, I will submit.

1 patch for repository code.haskell.org:/srv/code/XMonadContrib:

Fri Sep 26 01:02:15 PDT 2014  Devin Mullins <devinmullins@gmail.com>
  * X.A.Navigation2D: add convenience functions for setting config & keybindings
  Added 'navigation2D' which delegates to withNavigation2DConfig and
  additionalKeys, and 'navigation2DP' which is the 'additionalKeysP' version of
  the same.



[X.A.Navigation2D: add convenience functions for setting config & keybindings
Devin Mullins <devinmullins@gmail.com>**20140926080215
 Ignore-this: ab2c0b2a5255377420e5cc83b1dcd6a1
 Added 'navigation2D' which delegates to withNavigation2DConfig and
 additionalKeys, and 'navigation2DP' which is the 'additionalKeysP' version of
 the same.
] {
hunk ./XMonad/Actions/Navigation2D.hs 35
                                      -- * Exported functions and types
                                      -- #Exports#

-                                     withNavigation2DConfig
+                                     navigation2D
+                                   , navigation2DP
+                                   , withNavigation2DConfig
                                    , Navigation2DConfig(..)
                                    , def
                                    , defaultNavigation2DConfig
hunk ./XMonad/Actions/Navigation2D.hs 62
 import XMonad hiding (Screen)
 import qualified XMonad.StackSet as W
 import qualified XMonad.Util.ExtensibleState as XS
+import XMonad.Util.EZConfig (additionalKeys, additionalKeysP)
 import XMonad.Util.Types

 -- $usage
hunk ./XMonad/Actions/Navigation2D.hs 84
 --
 -- > import XMonad.Actions.Navigation2D
 --
--- Then edit your keybindings:
+-- Then add the configuration of the module to your main function:
+--
+-- > main = xmonad $ navigation2D def
+-- >                              (xK_Up, xK_Left, xK_Down, xK_Right)
+-- >                              [(mod4Mask,               windowGo  ),
+-- >                               (mod4Mask .|. shiftMask, windowSwap)]
+-- >                              False
+-- >               $ def
+--
+-- Alternatively, you can use navigation2DP:
+--
+-- > main = xmonad $ navigation2D def
+-- >                              ("<Up>", "<Left>", "<Down>", "<Right>")
+-- >                              [("M-",   windowGo  ),
+-- >                               ("M-S-", windowSwap)]
+-- >                              False
+-- >               $ def
+--
+-- That's it. If instead you'd like more control, you can specify your keybindings:
 --
 -- >    -- Switch between layers
hunk ./XMonad/Actions/Navigation2D.hs 105
--- >    , ((modm,                 xK_space), switchLayers)
+-- >    , ((modm,                 xK_space), switchLayer)
 -- >
 -- >    -- Directional navigation of windows
 -- >    , ((modm,                 xK_Right), windowGo R False)
hunk ./XMonad/Actions/Navigation2D.hs 330
 -- | Shorthand for the tedious screen type
 type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail

+-- | Convenience function for enabling Navigation2D with typical keybindings.
+-- Takes an (up, left, down, right) tuple, a mapping from modifier key to
+-- action, and a bool to indicate if wrapping should occur. Example:
+--
+-- >  navigation2D def (xK_w, xK_a, xK_s, xK_d) [(mod4Mask, windowGo), (mod4Mask .|. shiftMask, windowSwap)] False
+navigation2D :: Navigation2DConfig -> (KeySym, KeySym, KeySym, KeySym) -> [(ButtonMask, Direction2D -> Bool -> X ())] ->
+                Bool -> XConfig l -> XConfig l
+navigation2D navConfig (u, l, d, r) modifiers wrap xconfig =
+  withNavigation2DConfig navConfig xconfig
+  `additionalKeys`
+  [((modif, k), func dir wrap) | (modif, func) <- modifiers, (k, dir) <- dirKeys]
+  where dirKeys = [(u, U), (l, L), (d, D), (r, R)]
+
+-- | Convenience function for enabling Navigation2D with typical keybindings,
+-- using the syntax defined in 'XMonad.Util.EZConfig.mkKeymap'. Takes an (up,
+-- left, down, right) tuple, a mapping from key prefix to action, and a bool to
+-- indicate if wrapping should occur. Example:
+--
+-- >  navigation2DP def ("w", "a", "s", "d") [("M-", windowGo), ("M-S-", windowSwap)] False
+navigation2DP :: Navigation2DConfig -> (String, String, String, String) -> [(String, Direction2D -> Bool -> X ())] ->
+                 Bool -> XConfig l -> XConfig l
+navigation2DP navConfig (u, l, d, r) modifiers wrap xconfig =
+  withNavigation2DConfig navConfig xconfig
+  `additionalKeysP`
+  [(modif ++ k, func dir wrap) | (modif, func) <- modifiers, (k, dir) <- dirKeys]
+  where dirKeys = [(u, U), (l, L), (d, D), (r, R)]
+
 -- So we can store the configuration in extensible state
 instance ExtensionClass Navigation2DConfig where
   initialValue = def
}