{-# LANGUAGE CPP #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ScopedTypeVariables #-}
--------------------------------------------------------------------
-- |
-- Module      :  XMonad.Util.EZConfig
-- Description :  Configure key bindings easily in Emacs style.
-- Copyright   :  Devin Mullins <me@twifkak.com>
--                Brent Yorgey <byorgey@gmail.com> (key parsing)
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Devin Mullins <me@twifkak.com>
--
-- Useful helper functions for amending the default configuration, and for
-- parsing keybindings specified in a special (emacs-like) format.
--
-- (See also "XMonad.Util.CustomKeys" in xmonad-contrib.)
--
--------------------------------------------------------------------

module XMonad.Util.EZConfig (
                             -- * Usage
                             -- $usage

                             -- * Adding or removing keybindings

                             additionalKeys, additionalKeysP,
                             remapKeysP,
                             removeKeys, removeKeysP,
                             additionalMouseBindings, removeMouseBindings,

                             -- * Emacs-style keybinding specifications

                             mkKeymap, checkKeymap,
                             mkNamedKeymap,

                             -- * Parsers

                             parseKey, -- used by XMonad.Util.Paste
                             parseKeyCombo,
                             parseKeySequence, readKeySequence,
#ifdef TESTING
                             parseModifier,
#endif
                            ) where

import XMonad
import XMonad.Actions.Submap
import XMonad.Prelude

import XMonad.Util.NamedActions
import XMonad.Util.Parser

import Control.Arrow (first, (&&&))
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as M
import Data.Ord (comparing)
import Data.List.NonEmpty (nonEmpty)

-- $usage
-- To use this module, first import it into your @xmonad.hs@:
--
-- > import XMonad.Util.EZConfig
--
-- Then, use one of the provided functions to modify your
-- configuration.  You can use 'additionalKeys', 'removeKeys',
-- 'additionalMouseBindings', and 'removeMouseBindings' to easily add
-- and remove keybindings or mouse bindings.  You can use 'mkKeymap'
-- to create a keymap using emacs-style keybinding specifications
-- like @\"M-x\"@ instead of @(modMask, xK_x)@, or 'additionalKeysP'
-- and 'removeKeysP' to easily add or remove emacs-style keybindings.
-- If you use emacs-style keybindings, the 'checkKeymap' function is
-- provided, suitable for adding to your 'startupHook', which can warn
-- you of any parse errors or duplicate bindings in your keymap.
--
-- For more information and usage examples, see the documentation
-- provided with each exported function, and check the xmonad config
-- archive (<http://haskell.org/haskellwiki/Xmonad/Config_archive>)
-- for some real examples of use.

-- |
-- Add or override keybindings from the existing set. Example use:
--
-- > main = xmonad $ def { terminal = "urxvt" }
-- >                 `additionalKeys`
-- >                 [ ((mod1Mask, xK_m        ), spawn "echo 'Hi, mom!' | dzen2 -p 4")
-- >                 , ((mod1Mask, xK_BackSpace), withFocused hide) -- N.B. this is an absurd thing to do
-- >                 ]
--
-- This overrides the previous definition of mod-m.
--
-- Note that, unlike in xmonad 0.4 and previous, you can't use modMask to refer
-- to the modMask you configured earlier. You must specify mod1Mask (or
-- whichever), or add your own @myModMask = mod1Mask@ line.
additionalKeys :: XConfig a -> [((KeyMask, KeySym), X ())] -> XConfig a
additionalKeys :: forall (a :: * -> *).
XConfig a -> [((KeyMask, KeySym), X ())] -> XConfig a
additionalKeys XConfig a
conf [((KeyMask, KeySym), X ())]
keyList =
    XConfig a
conf { keys :: XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys = forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union (forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [((KeyMask, KeySym), X ())]
keyList) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys XConfig a
conf }
infixl 4 `additionalKeys`

-- | Like 'additionalKeys', except using short @String@ key
--   descriptors like @\"M-m\"@ instead of @(modMask, xK_m)@, as
--   described in the documentation for 'mkKeymap'.  For example:
--
-- > main = xmonad $ def { terminal = "urxvt" }
-- >                 `additionalKeysP`
-- >                 [ ("M-m", spawn "echo 'Hi, mom!' | dzen2 -p 4")
-- >                 , ("M-<Backspace>", withFocused hide) -- N.B. this is an absurd thing to do
-- >                 ]

additionalKeysP :: XConfig l -> [(String, X ())] -> XConfig l
additionalKeysP :: forall (l :: * -> *). XConfig l -> [(String, X ())] -> XConfig l
additionalKeysP XConfig l
conf [(String, X ())]
keyList =
    XConfig l
conf { keys :: XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys = \XConfig Layout
cnf -> forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union (forall (l :: * -> *).
XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ())
mkKeymap XConfig Layout
cnf [(String, X ())]
keyList) (forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys XConfig l
conf XConfig Layout
cnf) }
infixl 4 `additionalKeysP`

-- |
-- Remap keybindings from one binding to another.  More precisely, the
-- input list contains pairs of the form @(TO, FROM)@, and maps the
-- action bound to @FROM@ to the key @TO@.  For example, the following
-- would bind @"M-m"@ to what's bound to @"M-c"@ (which is to close the
-- focused window, in this case):
--
-- > main :: IO ()
-- > main = xmonad $ def `remapKeysP` [("M-m", "M-c")]
--
-- NOTE: Submaps are not transparent, and thus these keys can't be
-- accessed in this way: more explicitly, the @FROM@ string may **not**
-- be a submap.  However, the @TO@ can be a submap without problems.
-- This means that
--
-- > xmonad $ def `remapKeysP` [("M-m", "M-c a")]
--
-- is illegal (and indeed will just disregard the binding altogether),
-- while
--
-- > xmonad $ def `remapKeysP` [("M-c a", "M-m")]
--
-- is totally fine.
remapKeysP :: XConfig l -> [(String, String)] -> XConfig l
remapKeysP :: forall (l :: * -> *). XConfig l -> [(String, String)] -> XConfig l
remapKeysP XConfig l
conf [(String, String)]
keyList =
    XConfig l
conf { keys :: XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys = \XConfig Layout
cnf -> forall (l :: * -> *).
XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ())
mkKeymap XConfig Layout
cnf (XConfig Layout -> [(String, X ())]
keyList' XConfig Layout
cnf) forall a. Semigroup a => a -> a -> a
<> forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys XConfig l
conf XConfig Layout
cnf }
  where
   keyList' :: XConfig Layout -> [(String, X ())]
   keyList' :: XConfig Layout -> [(String, X ())]
keyList' XConfig Layout
cnf =
     forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\String
s -> case forall (l :: * -> *).
XConfig l -> String -> Maybe (NonEmpty (KeyMask, KeySym))
readKeySequence XConfig Layout
cnf String
s of
                                 Just ((KeyMask, KeySym)
ks :| []) -> forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys XConfig l
conf XConfig Layout
cnf forall k a. Ord k => Map k a -> k -> Maybe a
M.!? (KeyMask, KeySym)
ks
                                 Maybe (NonEmpty (KeyMask, KeySym))
_               -> forall a. Maybe a
Nothing))
              [(String, String)]
keyList
infixl 4 `remapKeysP`

-- |
-- Remove standard keybindings you're not using. Example use:
--
-- > main = xmonad $ def { terminal = "urxvt" }
-- >                 `removeKeys` [(mod1Mask .|. shiftMask, n) | n <- [xK_1 .. xK_9]]
removeKeys :: XConfig a -> [(KeyMask, KeySym)] -> XConfig a
removeKeys :: forall (a :: * -> *). XConfig a -> [(KeyMask, KeySym)] -> XConfig a
removeKeys XConfig a
conf [(KeyMask, KeySym)]
keyList =
    XConfig a
conf { keys :: XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys = \XConfig Layout
cnf -> forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall k a. Ord k => k -> Map k a -> Map k a
M.delete (forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys XConfig a
conf XConfig Layout
cnf) [(KeyMask, KeySym)]
keyList }
infixl 4 `removeKeys`

-- | Like 'removeKeys', except using short @String@ key descriptors
--   like @\"M-m\"@ instead of @(modMask, xK_m)@, as described in the
--   documentation for 'mkKeymap'. For example:
--
-- > main = xmonad $ def { terminal = "urxvt" }
-- >                 `removeKeysP` ["M-S-" ++ [n] | n <- ['1'..'9']]

removeKeysP :: XConfig l -> [String] -> XConfig l
removeKeysP :: forall (l :: * -> *). XConfig l -> [String] -> XConfig l
removeKeysP XConfig l
conf [String]
keyList =
    XConfig l
conf { keys :: XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys = \XConfig Layout
cnf -> forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys XConfig l
conf XConfig Layout
cnf forall k a b. Ord k => Map k a -> Map k b -> Map k a
`M.difference` forall (l :: * -> *).
XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ())
mkKeymap XConfig Layout
cnf (forall a b. (a -> b) -> [a] -> [b]
map (, forall (m :: * -> *) a. Monad m => a -> m a
return ()) [String]
keyList) }
infixl 4 `removeKeysP`

-- | Like 'additionalKeys', but for mouse bindings.
additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a
additionalMouseBindings :: forall (a :: * -> *).
XConfig a -> [((KeyMask, Button), KeySym -> X ())] -> XConfig a
additionalMouseBindings XConfig a
conf [((KeyMask, Button), KeySym -> X ())]
mouseBindingsList =
    XConfig a
conf { mouseBindings :: XConfig Layout -> Map (KeyMask, Button) (KeySym -> X ())
mouseBindings = forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union (forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [((KeyMask, Button), KeySym -> X ())]
mouseBindingsList) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (l :: * -> *).
XConfig l
-> XConfig Layout -> Map (KeyMask, Button) (KeySym -> X ())
mouseBindings XConfig a
conf }
infixl 4 `additionalMouseBindings`

-- | Like 'removeKeys', but for mouse bindings.
removeMouseBindings :: XConfig a -> [(ButtonMask, Button)] -> XConfig a
removeMouseBindings :: forall (a :: * -> *). XConfig a -> [(KeyMask, Button)] -> XConfig a
removeMouseBindings XConfig a
conf [(KeyMask, Button)]
mouseBindingList =
    XConfig a
conf { mouseBindings :: XConfig Layout -> Map (KeyMask, Button) (KeySym -> X ())
mouseBindings = \XConfig Layout
cnf -> forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall k a. Ord k => k -> Map k a -> Map k a
M.delete (forall (l :: * -> *).
XConfig l
-> XConfig Layout -> Map (KeyMask, Button) (KeySym -> X ())
mouseBindings XConfig a
conf XConfig Layout
cnf) [(KeyMask, Button)]
mouseBindingList }
infixl 4 `removeMouseBindings`


--------------------------------------------------------------
--  Keybinding parsing  ---------------------------------------
--------------------------------------------------------------

-- | Given a config (used to determine the proper modifier key to use)
--   and a list of @(String, X ())@ pairs, create a key map by parsing
--   the key sequence descriptions contained in the Strings.  The key
--   sequence descriptions are \"emacs-style\": @M-@, @C-@, @S-@, and
--   @M\#-@ denote mod, control, shift, and mod1-mod5 (where @\#@ is
--   replaced by the appropriate number) respectively.  Note that if
--   you want to make a keybinding using \'alt\' even though you use a
--   different key (like the \'windows\' key) for \'mod\', you can use
--   something like @\"M1-x\"@ for alt+x (check the output of @xmodmap@
--   to see which mod key \'alt\' is bound to). Some special keys can
--   also be specified by enclosing their name in angle brackets.
--
--   For example, @\"M-C-x\"@ denotes mod+ctrl+x; @\"S-\<Escape\>\"@
--   denotes shift-escape; @\"M1-C-\<Delete\>\"@ denotes alt+ctrl+delete
--   (assuming alt is bound to mod1, which is common).
--
--   Sequences of keys can also be specified by separating the key
--   descriptions with spaces. For example, @\"M-x y \<Down\>\"@ denotes the
--   sequence of keys mod+x, y, down.  Submaps (see
--   "XMonad.Actions.Submap") will be automatically generated to
--   correctly handle these cases.
--
--   So, for example, a complete key map might be specified as
--
-- > keys = \c -> mkKeymap c $
-- >     [ ("M-S-<Return>", spawn $ terminal c)
-- >     , ("M-x w", spawn "xmessage 'woohoo!'")  -- type mod+x then w to pop up 'woohoo!'
-- >     , ("M-x y", spawn "xmessage 'yay!'")     -- type mod+x then y to pop up 'yay!'
-- >     , ("M-S-c", kill)
-- >     ]
--
-- Alternatively, you can use 'additionalKeysP' to automatically
-- create a keymap and add it to your config.
--
-- Here is a complete list of supported special keys.  Note that a few
-- keys, such as the arrow keys, have synonyms.  If there are other
-- special keys you would like to see supported, feel free to submit a
-- patch, or ask on the xmonad mailing list; adding special keys is
-- quite simple.
--
-- > <Backspace>
-- > <Tab>
-- > <Return>
-- > <Pause>
-- > <Num_Lock>
-- > <Caps_Lock>
-- > <Scroll_lock>
-- > <Sys_Req>
-- > <Print>
-- > <Escape>, <Esc>
-- > <Delete>
-- > <Home>
-- > <Left>, <L>
-- > <Up>, <U>
-- > <Right>, <R>
-- > <Down>, <D>
-- > <Page_Up>
-- > <Page_Down>
-- > <End>
-- > <Insert>
-- > <Break>
-- > <Space>
-- > <Control_L>
-- > <Control_R>
-- > <Shift_L>
-- > <Shift_R>
-- > <Alt_L>
-- > <Alt_R>
-- > <Meta_L>
-- > <Meta_R>
-- > <Super_L>
-- > <Super_R>
-- > <Hyper_L>
-- > <Hyper_R>
-- > <F1>-<F24>
-- > <KP_Space>
-- > <KP_Tab>
-- > <KP_Enter>
-- > <KP_F1>
-- > <KP_F2>
-- > <KP_F3>
-- > <KP_F4>
-- > <KP_Home>
-- > <KP_Left>
-- > <KP_Up>
-- > <KP_Right>
-- > <KP_Down>
-- > <KP_Prior>
-- > <KP_Page_Up>
-- > <KP_Next>
-- > <KP_Page_Down>
-- > <KP_End>
-- > <KP_Begin>
-- > <KP_Insert>
-- > <KP_Delete>
-- > <KP_Equal>
-- > <KP_Multiply>
-- > <KP_Add>
-- > <KP_Separator>
-- > <KP_Subtract>
-- > <KP_Decimal>
-- > <KP_Divide>
-- > <KP_0>-<KP_9>
--
-- Long list of multimedia keys. Please note that not all keys may be
-- present in your particular setup although most likely they will do.
--
-- > <XF86ModeLock>
-- > <XF86MonBrightnessUp>
-- > <XF86MonBrightnessDown>
-- > <XF86KbdLightOnOff>
-- > <XF86KbdBrightnessUp>
-- > <XF86KbdBrightnessDown>
-- > <XF86Standby>
-- > <XF86AudioLowerVolume>
-- > <XF86AudioMute>
-- > <XF86AudioRaiseVolume>
-- > <XF86AudioPlay>
-- > <XF86AudioStop>
-- > <XF86AudioPrev>
-- > <XF86AudioNext>
-- > <XF86HomePage>
-- > <XF86Mail>
-- > <XF86Start>
-- > <XF86Search>
-- > <XF86AudioRecord>
-- > <XF86Calculator>
-- > <XF86Memo>
-- > <XF86ToDoList>
-- > <XF86Calendar>
-- > <XF86PowerDown>
-- > <XF86ContrastAdjust>
-- > <XF86RockerUp>
-- > <XF86RockerDown>
-- > <XF86RockerEnter>
-- > <XF86Back>
-- > <XF86Forward>
-- > <XF86Stop>
-- > <XF86Refresh>
-- > <XF86PowerOff>
-- > <XF86WakeUp>
-- > <XF86Eject>
-- > <XF86ScreenSaver>
-- > <XF86WWW>
-- > <XF86Sleep>
-- > <XF86Favorites>
-- > <XF86AudioPause>
-- > <XF86AudioMedia>
-- > <XF86MyComputer>
-- > <XF86VendorHome>
-- > <XF86LightBulb>
-- > <XF86Shop>
-- > <XF86History>
-- > <XF86OpenURL>
-- > <XF86AddFavorite>
-- > <XF86HotLinks>
-- > <XF86BrightnessAdjust>
-- > <XF86Finance>
-- > <XF86Community>
-- > <XF86AudioRewind>
-- > <XF86XF86BackForward>
-- > <XF86Launch0>-<XF86Launch9>, <XF86LaunchA>-<XF86LaunchF>
-- > <XF86ApplicationLeft>
-- > <XF86ApplicationRight>
-- > <XF86Book>
-- > <XF86CD>
-- > <XF86Calculater>
-- > <XF86Clear>
-- > <XF86Close>
-- > <XF86Copy>
-- > <XF86Cut>
-- > <XF86Display>
-- > <XF86DOS>
-- > <XF86Documents>
-- > <XF86Excel>
-- > <XF86Explorer>
-- > <XF86Game>
-- > <XF86Go>
-- > <XF86iTouch>
-- > <XF86LogOff>
-- > <XF86Market>
-- > <XF86Meeting>
-- > <XF86MenuKB>
-- > <XF86MenuPB>
-- > <XF86MySites>
-- > <XF86New>
-- > <XF86News>
-- > <XF86OfficeHome>
-- > <XF86Open>
-- > <XF86Option>
-- > <XF86Paste>
-- > <XF86Phone>
-- > <XF86Q>
-- > <XF86Reply>
-- > <XF86Reload>
-- > <XF86RotateWindows>
-- > <XF86RotationPB>
-- > <XF86RotationKB>
-- > <XF86Save>
-- > <XF86ScrollUp>
-- > <XF86ScrollDown>
-- > <XF86ScrollClick>
-- > <XF86Send>
-- > <XF86Spell>
-- > <XF86SplitScreen>
-- > <XF86Support>
-- > <XF86TaskPane>
-- > <XF86Terminal>
-- > <XF86Tools>
-- > <XF86Travel>
-- > <XF86UserPB>
-- > <XF86User1KB>
-- > <XF86User2KB>
-- > <XF86Video>
-- > <XF86WheelButton>
-- > <XF86Word>
-- > <XF86Xfer>
-- > <XF86ZoomIn>
-- > <XF86ZoomOut>
-- > <XF86Away>
-- > <XF86Messenger>
-- > <XF86WebCam>
-- > <XF86MailForward>
-- > <XF86Pictures>
-- > <XF86Music>
-- > <XF86TouchpadToggle>
-- > <XF86AudioMicMute>
-- > <XF86_Switch_VT_1>-<XF86_Switch_VT_12>
-- > <XF86_Ungrab>
-- > <XF86_ClearGrab>
-- > <XF86_Next_VMode>
-- > <XF86_Prev_VMode>
-- > <XF86Bluetooth>

mkKeymap :: XConfig l -> [(String, X ())] -> M.Map (KeyMask, KeySym) (X ())
mkKeymap :: forall (l :: * -> *).
XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ())
mkKeymap XConfig l
c = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(NonEmpty (KeyMask, KeySym), X ())] -> [((KeyMask, KeySym), X ())]
mkSubmaps forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (l :: * -> *) t.
XConfig l -> [(String, t)] -> [(NonEmpty (KeyMask, KeySym), t)]
readKeymap XConfig l
c

mkNamedKeymap :: XConfig l -> [(String, NamedAction)] -> [((KeyMask, KeySym), NamedAction)]
mkNamedKeymap :: forall (l :: * -> *).
XConfig l
-> [(String, NamedAction)] -> [((KeyMask, KeySym), NamedAction)]
mkNamedKeymap XConfig l
c = [(NonEmpty (KeyMask, KeySym), NamedAction)]
-> [((KeyMask, KeySym), NamedAction)]
mkNamedSubmaps forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (l :: * -> *) t.
XConfig l -> [(String, t)] -> [(NonEmpty (KeyMask, KeySym), t)]
readKeymap XConfig l
c

-- | Given a list of pairs of parsed key sequences and actions,
--   group them into submaps in the appropriate way.

mkNamedSubmaps :: [(NonEmpty (KeyMask, KeySym), NamedAction)] -> [((KeyMask, KeySym), NamedAction)]
mkNamedSubmaps :: [(NonEmpty (KeyMask, KeySym), NamedAction)]
-> [((KeyMask, KeySym), NamedAction)]
mkNamedSubmaps = forall a b.
Ord a =>
([(a, b)] -> b) -> [(NonEmpty a, b)] -> [(a, b)]
mkSubmaps' forall a. HasName a => [((KeyMask, KeySym), a)] -> NamedAction
submapName

mkSubmaps :: [ (NonEmpty (KeyMask, KeySym), X ()) ] -> [((KeyMask, KeySym), X ())]
mkSubmaps :: [(NonEmpty (KeyMask, KeySym), X ())] -> [((KeyMask, KeySym), X ())]
mkSubmaps = forall a b.
Ord a =>
([(a, b)] -> b) -> [(NonEmpty a, b)] -> [(a, b)]
mkSubmaps' forall a b. (a -> b) -> a -> b
$ Map (KeyMask, KeySym) (X ()) -> X ()
submap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Ord k => [(k, a)] -> Map k a
M.fromList

mkSubmaps' :: forall a b. (Ord a) => ([(a, b)] -> b) -> [(NonEmpty a, b)] -> [(a, b)]
mkSubmaps' :: forall a b.
Ord a =>
([(a, b)] -> b) -> [(NonEmpty a, b)] -> [(a, b)]
mkSubmaps' [(a, b)] -> b
subm [(NonEmpty a, b)]
binds = forall a b. (a -> b) -> [a] -> [b]
map [(NonEmpty a, b)] -> (a, b)
combine [[(NonEmpty a, b)]]
gathered
  where
   gathered :: [[(NonEmpty a, b)]]
   gathered :: [[(NonEmpty a, b)]]
gathered = forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (NonEmpty a, b) -> (NonEmpty a, b) -> Bool
fstKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$ [(NonEmpty a, b)]
binds

   combine :: [(NonEmpty a, b)] -> (a, b)
   combine :: [(NonEmpty a, b)] -> (a, b)
combine [(a
k :| [], b
act)] = (a
k, b
act)
   combine [(NonEmpty a, b)]
ks = ( forall a. NonEmpty a -> a
NE.head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> a
NE.head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasCallStack => [a] -> NonEmpty a
notEmpty forall a b. (a -> b) -> a -> b
$ [(NonEmpty a, b)]
ks
                , [(a, b)] -> b
subm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b.
Ord a =>
([(a, b)] -> b) -> [(NonEmpty a, b)] -> [(a, b)]
mkSubmaps' [(a, b)] -> b
subm forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (forall a. HasCallStack => [a] -> NonEmpty a
notEmpty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> NonEmpty a -> [a]
NE.drop Int
1)) [(NonEmpty a, b)]
ks
                )

   fstKey :: (NonEmpty a, b) -> (NonEmpty a, b) -> Bool
   fstKey :: (NonEmpty a, b) -> (NonEmpty a, b) -> Bool
fstKey = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (forall a. NonEmpty a -> a
NE.head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)

-- | Given a configuration record and a list of (key sequence
--   description, action) pairs, parse the key sequences into lists of
--   @(KeyMask,KeySym)@ pairs.  Key sequences which fail to parse will
--   be ignored.
readKeymap :: XConfig l -> [(String, t)] -> [(NonEmpty (KeyMask, KeySym), t)]
readKeymap :: forall (l :: * -> *) t.
XConfig l -> [(String, t)] -> [(NonEmpty (KeyMask, KeySym), t)]
readKeymap XConfig l
c = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall {a} {b}. (Maybe a, b) -> Maybe (a, b)
maybeKeys forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (forall (l :: * -> *).
XConfig l -> String -> Maybe (NonEmpty (KeyMask, KeySym))
readKeySequence XConfig l
c))
  where maybeKeys :: (Maybe a, b) -> Maybe (a, b)
maybeKeys (Maybe a
Nothing,b
_) = forall a. Maybe a
Nothing
        maybeKeys (Just a
k, b
act) = forall a. a -> Maybe a
Just (a
k, b
act)

-- | Parse a sequence of keys, returning Nothing if there is
--   a parse failure (no parse, or ambiguous parse).
readKeySequence :: XConfig l -> String -> Maybe (NonEmpty (KeyMask, KeySym))
readKeySequence :: forall (l :: * -> *).
XConfig l -> String -> Maybe (NonEmpty (KeyMask, KeySym))
readKeySequence XConfig l
c = forall a. [a] -> Maybe (NonEmpty a)
nonEmpty forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< forall a. Parser a -> String -> Maybe a
runParser (forall (l :: * -> *). XConfig l -> Parser [(KeyMask, KeySym)]
parseKeySequence XConfig l
c forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
eof)

-- | Parse a sequence of key combinations separated by spaces, e.g.
--   @\"M-c x C-S-2\"@ (mod+c, x, ctrl+shift+2).
parseKeySequence :: XConfig l -> Parser [(KeyMask, KeySym)]
parseKeySequence :: forall (l :: * -> *). XConfig l -> Parser [(KeyMask, KeySym)]
parseKeySequence XConfig l
c = forall (l :: * -> *). XConfig l -> Parser (KeyMask, KeySym)
parseKeyCombo XConfig l
c forall a sep. Parser a -> Parser sep -> Parser [a]
`sepBy1` forall a. Parser a -> Parser [a]
many1 (Char -> Parser Char
char Char
' ')

-- | Parse a modifier-key combination such as "M-C-s" (mod+ctrl+s).
parseKeyCombo :: XConfig l -> Parser (KeyMask, KeySym)
parseKeyCombo :: forall (l :: * -> *). XConfig l -> Parser (KeyMask, KeySym)
parseKeyCombo XConfig l
c = do [KeyMask]
mods <- forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall (l :: * -> *). XConfig l -> Parser KeyMask
parseModifier XConfig l
c)
                     KeySym
k <- Parser KeySym
parseKey
                     forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall a. Bits a => a -> a -> a
(.|.) KeyMask
0 [KeyMask]
mods, KeySym
k)

-- | Parse a modifier: either M- (user-defined mod-key),
--   C- (control), S- (shift), or M#- where # is an integer
--   from 1 to 5 (mod1Mask through mod5Mask).
parseModifier :: XConfig l -> Parser KeyMask
parseModifier :: forall (l :: * -> *). XConfig l -> Parser KeyMask
parseModifier XConfig l
c = (String -> Parser String
string String
"M-" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall (l :: * -> *). XConfig l -> KeyMask
modMask XConfig l
c)
               forall a. Semigroup a => a -> a -> a
<> (String -> Parser String
string String
"C-" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> KeyMask
controlMask)
               forall a. Semigroup a => a -> a -> a
<> (String -> Parser String
string String
"S-" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> KeyMask
shiftMask)
               forall a. Semigroup a => a -> a -> a
<> do Char
_ <- Char -> Parser Char
char Char
'M'
                     Char
n <- (Char -> Bool) -> Parser Char
satisfy (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'1'..Char
'5'])
                     Char
_ <- Char -> Parser Char
char Char
'-'
                     forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> KeyMask
indexMod (forall a. Read a => String -> a
read [Char
n] forall a. Num a => a -> a -> a
- Int
1)
    where indexMod :: Int -> KeyMask
indexMod = forall a. [a] -> Int -> a
(!!) [KeyMask
mod1Mask,KeyMask
mod2Mask,KeyMask
mod3Mask,KeyMask
mod4Mask,KeyMask
mod5Mask]

-- | Parse an unmodified basic key, like @\"x\"@, @\"\<F1\>\"@, etc.
parseKey :: Parser KeySym
parseKey :: Parser KeySym
parseKey = Parser KeySym
parseSpecial forall a. Semigroup a => a -> a -> a
<> Parser KeySym
parseRegular

-- | Parse a regular key name (represented by itself).
parseRegular :: Parser KeySym
parseRegular :: Parser KeySym
parseRegular = forall a. [Parser a] -> Parser a
choice [ String -> Parser String
string String
s forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> KeySym
k | (String
s, KeySym
k) <- [(String, KeySym)]
regularKeys ]

-- | Parse a special key name (one enclosed in angle brackets).
parseSpecial :: Parser KeySym
parseSpecial :: Parser KeySym
parseSpecial = do Char
_ <- Char -> Parser Char
char Char
'<'
                  forall a. [Parser a] -> Parser a
choice [ KeySym
k forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
string String
name forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Char
char Char
'>'
                         | (String
name, KeySym
k) <- [(String, KeySym)]
allSpecialKeys
                         ]

-- | Given a configuration record and a list of (key sequence
--   description, action) pairs, check the key sequence descriptions
--   for validity, and warn the user (via a popup xmessage window) of
--   any unparseable or duplicate key sequences.  This function is
--   appropriate for adding to your @startupHook@, and you are highly
--   encouraged to do so; otherwise, duplicate or unparseable
--   keybindings will be silently ignored.
--
--   For example, you might do something like this:
--
-- > main = xmonad $ myConfig
-- >
-- > myKeymap = [("S-M-c", kill), ...]
-- > myConfig = def {
-- >     ...
-- >     keys = \c -> mkKeymap c myKeymap
-- >     startupHook = return () >> checkKeymap myConfig myKeymap
-- >     ...
-- > }
--
-- NOTE: the @return ()@ in the example above is very important!
-- Otherwise, you might run into problems with infinite mutual
-- recursion: the definition of myConfig depends on the definition of
-- startupHook, which depends on the definition of myConfig, ... and
-- so on.  Actually, it's likely that the above example in particular
-- would be OK without the @return ()@, but making @myKeymap@ take
-- @myConfig@ as a parameter would definitely lead to
-- problems. Believe me.  It, uh, happened to my friend. In... a
-- dream. Yeah. In any event, the @return () >>@ introduces enough
-- laziness to break the deadlock.
--
checkKeymap :: XConfig l -> [(String, a)] -> X ()
checkKeymap :: forall (l :: * -> *) a. XConfig l -> [(String, a)] -> X ()
checkKeymap XConfig l
conf [(String, a)]
km = forall {m :: * -> *}. MonadIO m => ([String], [String]) -> m ()
warn (forall (l :: * -> *) a.
XConfig l -> [(String, a)] -> ([String], [String])
doKeymapCheck XConfig l
conf [(String, a)]
km)
  where warn :: ([String], [String]) -> m ()
warn ([],[])   = forall (m :: * -> *) a. Monad m => a -> m a
return ()
        warn ([String]
bad,[String]
dup) = forall (m :: * -> *). MonadIO m => String -> m ()
xmessage forall a b. (a -> b) -> a -> b
$ String
"Warning:\n"
                            forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
msg String
"bad" [String]
bad forall a. [a] -> [a] -> [a]
++ String
"\n"
                            forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
msg String
"duplicate" [String]
dup
        msg :: String -> [String] -> String
msg String
_ [] = String
""
        msg String
m [String]
xs = String
m forall a. [a] -> [a] -> [a]
++ String
" keybindings detected: " forall a. [a] -> [a] -> [a]
++ [String] -> String
showBindings [String]
xs
        showBindings :: [String] -> String
showBindings = [String] -> String
unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map ((String
"\""forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. [a] -> [a] -> [a]
++String
"\""))

-- | Given a config and a list of (key sequence description, action)
--   pairs, check the key sequence descriptions for validity,
--   returning a list of unparseable key sequences, and a list of
--   duplicate key sequences.
doKeymapCheck :: XConfig l -> [(String,a)] -> ([String], [String])
doKeymapCheck :: forall (l :: * -> *) a.
XConfig l -> [(String, a)] -> ([String], [String])
doKeymapCheck XConfig l
conf [(String, a)]
km = ([String]
bad,[String]
dups)
  where ks :: [(Maybe (NonEmpty (KeyMask, KeySym)), String)]
ks = forall a b. (a -> b) -> [a] -> [b]
map ((forall (l :: * -> *).
XConfig l -> String -> Maybe (NonEmpty (KeyMask, KeySym))
readKeySequence XConfig l
conf forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(String, a)]
km
        bad :: [String]
bad = forall a. Eq a => [a] -> [a]
nub forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$ [(Maybe (NonEmpty (KeyMask, KeySym)), String)]
ks
        dups :: [String]
dups = forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> a
NE.head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasCallStack => [a] -> NonEmpty a
notEmpty)
             forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Ord a => a -> a -> Bool
>Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length)
             forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a, b) -> a
fst)
             forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing forall a b. (a, b) -> a
fst)
             forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall a. HasCallStack => Maybe a -> a
fromJust)
             forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
             forall a b. (a -> b) -> a -> b
$ [(Maybe (NonEmpty (KeyMask, KeySym)), String)]
ks