Skip to content

Commit

Permalink
Merge pull request #888 from andwu137/master
Browse files Browse the repository at this point in the history
Add a method to re-sort keys for visualSubmap
  • Loading branch information
slotThe authored May 9, 2024
2 parents cbdee7d + abef527 commit 8fb1973
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 4 deletions.
5 changes: 5 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,11 @@
(See also `XMonad.Hooks.FloatConfigureReq` and/or `XMonad.Util.Hacks`
for additional Steam client workarounds.)

* `XMonad.Actions.Submap`

- Added `visualSubmapSorted` to enable sorting of the keymap
descriptions.

### Other changes

## 0.18.0 (February 3, 2024)
Expand Down
26 changes: 22 additions & 4 deletions XMonad/Actions/Submap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module XMonad.Actions.Submap (
-- $usage
submap,
visualSubmap,
visualSubmapSorted,
submapDefault,
submapDefaultWithKey,

Expand Down Expand Up @@ -88,15 +89,32 @@ visualSubmap :: WindowConfig -- ^ The config for the spawned window.
-> M.Map (KeyMask, KeySym) (String, X ())
-- ^ A map @keybinding -> (description, action)@.
-> X ()
visualSubmap wc keys =
visualSubmap = visualSubmapSorted id

-- | Like 'visualSubmap', but is able to sort the descriptions.
-- For example,
--
-- > import Data.Ord (comparing, Down)
-- >
-- > visualSubmapSorted (sortBy (comparing Down)) def
--
-- would sort the @(key, description)@ pairs by their keys in descending
-- order.
visualSubmapSorted :: ([((KeyMask, KeySym), String)] -> [((KeyMask, KeySym), String)])
-- ^ A function to resort the descriptions
-> WindowConfig -- ^ The config for the spawned window.
-> M.Map (KeyMask, KeySym) (String, X ())
-- ^ A map @keybinding -> (description, action)@.
-> X ()
visualSubmapSorted sorted wc keys =
withSimpleWindow wc descriptions waitForKeyPress >>= \(m', s) ->
maybe (pure ()) snd (M.lookup (m', s) keys)
where
descriptions :: [String]
descriptions =
zipWith (\key desc -> keyToString key <> ": " <> desc)
(M.keys keys)
(map fst (M.elems keys))
map (\(key, desc) -> keyToString key <> ": " <> desc)
. sorted
$ zip (M.keys keys) (map fst (M.elems keys))

-- | Give a name to an action.
subName :: String -> X () -> (String, X ())
Expand Down

0 comments on commit 8fb1973

Please sign in to comment.