mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-01 12:41:52 -07:00
X.A.EasyMotion: consistent indentation, hlint nits
This commit is contained in:
@@ -212,9 +212,9 @@ proportional f th r = Rectangle { rect_width = newW
|
|||||||
, rect_height = newH
|
, rect_height = newH
|
||||||
, rect_x = rect_x r + fi (rect_width r - newW) `div` 2
|
, rect_x = rect_x r + fi (rect_width r - newW) `div` 2
|
||||||
, rect_y = rect_y r + fi (rect_height r - newH) `div` 2 }
|
, rect_y = rect_y r + fi (rect_height r - newH) `div` 2 }
|
||||||
where
|
where
|
||||||
newH = max (fi th) (round $ f * fi (rect_height r))
|
newH = max (fi th) (round $ f * fi (rect_height r))
|
||||||
newW = newH
|
newW = newH
|
||||||
|
|
||||||
-- | Create fixed-size overlay windows
|
-- | Create fixed-size overlay windows
|
||||||
fixedSize :: (Integral a, Integral b) => a -> b -> Position -> Rectangle -> Rectangle
|
fixedSize :: (Integral a, Integral b) => a -> b -> Position -> Rectangle -> Rectangle
|
||||||
@@ -222,9 +222,9 @@ fixedSize w h th r = Rectangle { rect_width = rw
|
|||||||
, rect_height = rh
|
, rect_height = rh
|
||||||
, rect_x = rect_x r + fi (rect_width r - rw) `div` 2
|
, rect_x = rect_x r + fi (rect_width r - rw) `div` 2
|
||||||
, rect_y = rect_y r + fi (rect_height r - rh) `div` 2 }
|
, rect_y = rect_y r + fi (rect_height r - rh) `div` 2 }
|
||||||
where
|
where
|
||||||
rw = max (fi w) (fi th)
|
rw = max (fi w) (fi th)
|
||||||
rh = max (fi h) (fi th)
|
rh = max (fi h) (fi th)
|
||||||
|
|
||||||
-- | Create overlay windows the minimum size to contain their key chord
|
-- | Create overlay windows the minimum size to contain their key chord
|
||||||
textSize :: Position -> Rectangle -> Rectangle
|
textSize :: Position -> Rectangle -> Rectangle
|
||||||
@@ -240,40 +240,41 @@ bar f th r = Rectangle { rect_width = rect_width r
|
|||||||
, rect_height = fi th
|
, rect_height = fi th
|
||||||
, rect_x = rect_x r
|
, rect_x = rect_x r
|
||||||
, rect_y = rect_y r + round (f' * (fi (rect_height r) - fi th)) }
|
, rect_y = rect_y r + round (f' * (fi (rect_height r) - fi th)) }
|
||||||
-- clamp f in [0,1] as other values will appear to lock up xmonad as the overlay will be
|
where
|
||||||
-- displayed off-screen
|
-- clamp f in [0,1] as other values will appear to lock up xmonad as the overlay will be
|
||||||
where f' = min 0.0 $ max f 1.0
|
-- displayed off-screen
|
||||||
|
f' = min 0.0 $ max f 1.0
|
||||||
|
|
||||||
-- | Handles overlay display and window selection. Called after config has been sanitised.
|
-- | Handles overlay display and window selection. Called after config has been sanitised.
|
||||||
handleSelectWindow :: EasyMotionConfig -> X (Maybe Window)
|
handleSelectWindow :: EasyMotionConfig -> X (Maybe Window)
|
||||||
handleSelectWindow EMConf { sKeys = AnyKeys [] } = return Nothing
|
handleSelectWindow EMConf { sKeys = AnyKeys [] } = return Nothing
|
||||||
handleSelectWindow c = do
|
handleSelectWindow c = do
|
||||||
f <- initXMF $ font c
|
f <- initXMF $ font c
|
||||||
th <- (\(asc, dsc) -> asc + dsc + 2) <$> (textExtentsXMF f (concatMap keysymToString (allKeys . sKeys $ c)))
|
th <- (\(asc, dsc) -> asc + dsc + 2) <$> textExtentsXMF f (concatMap keysymToString (allKeys . sKeys $ c))
|
||||||
XConf { theRoot = rw, display = dpy } <- ask
|
XConf { theRoot = rw, display = dpy } <- ask
|
||||||
XState { mapped = mappedWins, windowset = ws } <- get
|
XState { mapped = mappedWins, windowset = ws } <- get
|
||||||
-- build overlays depending on key configuration
|
-- build overlays depending on key configuration
|
||||||
overlays :: [Overlay] <- case sKeys c of
|
overlays :: [Overlay] <- case sKeys c of
|
||||||
AnyKeys ks -> buildOverlays ks <$> sortedOverlayWindows
|
AnyKeys ks -> buildOverlays ks <$> sortedOverlayWindows
|
||||||
where
|
where
|
||||||
visibleWindows :: [Window]
|
visibleWindows :: [Window]
|
||||||
visibleWindows = toList mappedWins
|
visibleWindows = toList mappedWins
|
||||||
sortedOverlayWindows :: X [OverlayWindow]
|
sortedOverlayWindows :: X [OverlayWindow]
|
||||||
sortedOverlayWindows = sortOverlayWindows <$> buildOverlayWindows dpy th visibleWindows
|
sortedOverlayWindows = sortOverlayWindows <$> buildOverlayWindows dpy th visibleWindows
|
||||||
PerScreenKeys m ->
|
PerScreenKeys m ->
|
||||||
fmap concat
|
fmap concat
|
||||||
$ sequence
|
$ sequence
|
||||||
$ M.foldr (:) []
|
$ M.foldr (:) []
|
||||||
$ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m
|
$ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m
|
||||||
where
|
where
|
||||||
screenById :: ScreenId -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail)
|
screenById :: ScreenId -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail)
|
||||||
screenById sid = L.find ((== sid) . screen) (W.current ws : W.visible ws)
|
screenById sid = L.find ((== sid) . screen) (W.current ws : W.visible ws)
|
||||||
visibleWindowsOnScreen :: ScreenId -> [Window]
|
visibleWindowsOnScreen :: ScreenId -> [Window]
|
||||||
visibleWindowsOnScreen sid = L.filter (`elem` (toList mappedWins)) $ W.integrate' $ (screenById sid) >>= W.stack . W.workspace
|
visibleWindowsOnScreen sid = L.filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace
|
||||||
sortedOverlayWindows :: ScreenId -> X [OverlayWindow]
|
sortedOverlayWindows :: ScreenId -> X [OverlayWindow]
|
||||||
sortedOverlayWindows sid = sortOverlayWindows <$> (buildOverlayWindows dpy th $ visibleWindowsOnScreen sid)
|
sortedOverlayWindows sid = sortOverlayWindows <$> buildOverlayWindows dpy th (visibleWindowsOnScreen sid)
|
||||||
status <- io $ grabKeyboard dpy rw True grabModeAsync grabModeAsync currentTime
|
status <- io $ grabKeyboard dpy rw True grabModeAsync grabModeAsync currentTime
|
||||||
if (status == grabSuccess)
|
if status == grabSuccess
|
||||||
then do
|
then do
|
||||||
resultWin <- handleKeyboard dpy (displayOverlay f) (cancelKey c) overlays []
|
resultWin <- handleKeyboard dpy (displayOverlay f) (cancelKey c) overlays []
|
||||||
io $ ungrabKeyboard dpy currentTime
|
io $ ungrabKeyboard dpy currentTime
|
||||||
@@ -284,71 +285,72 @@ handleSelectWindow c = do
|
|||||||
-- focus the selected window
|
-- focus the selected window
|
||||||
Selected o -> return . Just . win . overlayWin $ o
|
Selected o -> return . Just . win . overlayWin $ o
|
||||||
-- return focus correctly
|
-- return focus correctly
|
||||||
_ -> whenJust (W.peek ws :: Maybe Window) (windows . W.focusWindow) >> return Nothing
|
_ -> whenJust (W.peek ws) (windows . W.focusWindow) >> return Nothing
|
||||||
else releaseXMF f >> return Nothing
|
else releaseXMF f >> return Nothing
|
||||||
where
|
where
|
||||||
allKeys :: ChordKeys -> [KeySym]
|
allKeys :: ChordKeys -> [KeySym]
|
||||||
allKeys (AnyKeys ks) = ks
|
allKeys (AnyKeys ks) = ks
|
||||||
allKeys (PerScreenKeys m) = concat $ M.foldr (:) [] m
|
allKeys (PerScreenKeys m) = concat $ M.foldr (:) [] m
|
||||||
|
|
||||||
buildOverlays :: [KeySym] -> [OverlayWindow] -> [Overlay]
|
buildOverlays :: [KeySym] -> [OverlayWindow] -> [Overlay]
|
||||||
buildOverlays ks = appendChords (maxChordLen c) ks
|
buildOverlays ks = appendChords (maxChordLen c) ks
|
||||||
|
|
||||||
buildOverlayWindows :: Display -> Position -> [Window] -> X [OverlayWindow]
|
buildOverlayWindows :: Display -> Position -> [Window] -> X [OverlayWindow]
|
||||||
buildOverlayWindows dpy th ws = sequence $ (buildOverlayWin dpy th) <$> ws
|
buildOverlayWindows dpy th ws = sequence $ buildOverlayWin dpy th <$> ws
|
||||||
|
|
||||||
sortOverlayWindows :: [OverlayWindow] -> [OverlayWindow]
|
sortOverlayWindows :: [OverlayWindow] -> [OverlayWindow]
|
||||||
sortOverlayWindows = (sortOn ((wa_x &&& wa_y) . attrs))
|
sortOverlayWindows = sortOn ((wa_x &&& wa_y) . attrs)
|
||||||
|
|
||||||
makeRect :: WindowAttributes -> Rectangle
|
makeRect :: WindowAttributes -> Rectangle
|
||||||
makeRect wa = Rectangle (fi (wa_x wa)) (fi (wa_y wa)) (fi (wa_width wa)) (fi (wa_height wa))
|
makeRect wa = Rectangle (fi (wa_x wa)) (fi (wa_y wa)) (fi (wa_width wa)) (fi (wa_height wa))
|
||||||
|
|
||||||
buildOverlayWin :: Display -> Position -> Window -> X OverlayWindow
|
buildOverlayWin :: Display -> Position -> Window -> X OverlayWindow
|
||||||
buildOverlayWin dpy th w = do
|
buildOverlayWin dpy th w = do
|
||||||
wAttrs <- io $ getWindowAttributes dpy w
|
wAttrs <- io $ getWindowAttributes dpy w
|
||||||
let r = overlayF c th $ makeRect wAttrs
|
let r = overlayF c th $ makeRect wAttrs
|
||||||
o <- createNewWindow r Nothing "" True
|
o <- createNewWindow r Nothing "" True
|
||||||
return OverlayWindow { rect=r, overlay=o, win=w, attrs=wAttrs }
|
return OverlayWindow { rect=r, overlay=o, win=w, attrs=wAttrs }
|
||||||
|
|
||||||
-- | Display an overlay with the provided formatting
|
-- | Display an overlay with the provided formatting
|
||||||
displayOverlay :: XMonadFont -> Overlay -> X ()
|
displayOverlay :: XMonadFont -> Overlay -> X ()
|
||||||
displayOverlay f Overlay { overlayWin = OverlayWindow { rect = r, overlay = o }, chord = ch } = do
|
displayOverlay f Overlay { overlayWin = OverlayWindow { rect = r, overlay = o }, chord = ch } = do
|
||||||
showWindow o
|
showWindow o
|
||||||
paintAndWrite o f (fi (rect_width r)) (fi (rect_height r)) (fi (borderPx c)) (bgCol c) (borderCol c) (txtCol c) (bgCol c) [AlignCenter] [concatMap keysymToString ch]
|
paintAndWrite o f (fi (rect_width r)) (fi (rect_height r)) (fi (borderPx c)) (bgCol c) (borderCol c) (txtCol c) (bgCol c) [AlignCenter] [concatMap keysymToString ch]
|
||||||
|
|
||||||
-- | Display overlay windows and chords for window selection
|
-- | Display overlay windows and chords for window selection
|
||||||
selectWindow :: EasyMotionConfig -> X (Maybe Window)
|
selectWindow :: EasyMotionConfig -> X (Maybe Window)
|
||||||
selectWindow conf =
|
selectWindow conf =
|
||||||
handleSelectWindow conf { sKeys = sanitiseKeys (sKeys conf) }
|
handleSelectWindow conf { sKeys = sanitiseKeys (sKeys conf) }
|
||||||
where
|
where
|
||||||
-- make sure the key lists don't contain: backspace, or duplicates
|
-- make sure the key lists don't contain: backspace, or duplicates
|
||||||
sanitise :: [KeySym] -> [KeySym]
|
sanitise :: [KeySym] -> [KeySym]
|
||||||
sanitise = L.nub . L.filter (`notElem` [xK_BackSpace, cancelKey conf])
|
sanitise = L.nub . L.filter (`notElem` [xK_BackSpace, cancelKey conf])
|
||||||
sanitiseKeys :: ChordKeys -> ChordKeys
|
sanitiseKeys :: ChordKeys -> ChordKeys
|
||||||
sanitiseKeys cKeys =
|
sanitiseKeys cKeys =
|
||||||
case cKeys of
|
case cKeys of
|
||||||
AnyKeys ks -> AnyKeys . sanitise $ ks
|
AnyKeys ks -> AnyKeys . sanitise $ ks
|
||||||
PerScreenKeys m -> PerScreenKeys $ M.map sanitise m
|
PerScreenKeys m -> PerScreenKeys $ M.map sanitise m
|
||||||
|
|
||||||
-- | Take a list of overlays lacking chords, return a list of overlays with key chords
|
-- | Take a list of overlays lacking chords, return a list of overlays with key chords
|
||||||
appendChords :: Int -> [KeySym] -> [OverlayWindow] -> [Overlay]
|
appendChords :: Int -> [KeySym] -> [OverlayWindow] -> [Overlay]
|
||||||
appendChords _ [] _ = []
|
appendChords _ [] _ = []
|
||||||
appendChords maxUserSelectedLen ks overlayWins =
|
appendChords maxUserSelectedLen ks overlayWins =
|
||||||
zipWith (\ow c -> Overlay { overlayWin=ow, chord=c }) overlayWins chords
|
zipWith (\ow c -> Overlay { overlayWin=ow, chord=c }) overlayWins chords
|
||||||
where
|
where
|
||||||
chords = replicateM chordLen ks
|
chords = replicateM chordLen ks
|
||||||
-- the minimum necessary chord length to assign a unique chord to each visible window
|
-- the minimum necessary chord length to assign a unique chord to each visible window
|
||||||
minCoverLen = -((-(length overlayWins)) `div` length ks)
|
minCoverLen = -((-(length overlayWins)) `div` length ks)
|
||||||
-- if the user has specified a max chord length we use this even if it will not cover all
|
-- if the user has specified a max chord length we use this even if it will not cover all
|
||||||
-- windows, as they may prefer to focus windows with fewer keys over the ability to focus any
|
-- windows, as they may prefer to focus windows with fewer keys over the ability to focus any
|
||||||
-- window
|
-- window
|
||||||
chordLen = if maxUserSelectedLen <= 0 then minCoverLen else min minCoverLen maxUserSelectedLen
|
chordLen = if maxUserSelectedLen <= 0 then minCoverLen else min minCoverLen maxUserSelectedLen
|
||||||
|
|
||||||
-- | A three-state result for handling user-initiated selection cancellation, successful selection,
|
-- | A three-state result for handling user-initiated selection cancellation, successful selection,
|
||||||
-- or backspace.
|
-- or backspace.
|
||||||
data HandleResult = Exit | Selected Overlay | Backspace
|
data HandleResult = Exit | Selected Overlay | Backspace
|
||||||
|
|
||||||
-- | Handle key press events for window selection.
|
-- | Handle key press events for window selection.
|
||||||
handleKeyboard :: Display -> (Overlay -> X()) -> KeySym -> [Overlay] -> [Overlay] -> X (HandleResult)
|
handleKeyboard :: Display -> (Overlay -> X()) -> KeySym -> [Overlay] -> [Overlay] -> X HandleResult
|
||||||
handleKeyboard _ _ _ [] _ = return Exit
|
handleKeyboard _ _ _ [] _ = return Exit
|
||||||
handleKeyboard dpy drawFn cancel selected deselected = do
|
handleKeyboard dpy drawFn cancel selected deselected = do
|
||||||
redraw
|
redraw
|
||||||
@@ -365,18 +367,18 @@ handleKeyboard dpy drawFn cancel selected deselected = do
|
|||||||
io $ allowEvents dpy replayPointer currentTime
|
io $ allowEvents dpy replayPointer currentTime
|
||||||
handleKeyboard dpy drawFn cancel selected deselected
|
handleKeyboard dpy drawFn cancel selected deselected
|
||||||
| otherwise -> handleKeyboard dpy drawFn cancel selected deselected
|
| otherwise -> handleKeyboard dpy drawFn cancel selected deselected
|
||||||
where
|
where
|
||||||
redraw = mapM (mapM_ drawFn) [selected, deselected]
|
redraw = mapM (mapM_ drawFn) [selected, deselected]
|
||||||
retryBackspace x =
|
retryBackspace x =
|
||||||
case x of
|
case x of
|
||||||
Backspace -> redraw >> handleKeyboard dpy drawFn cancel selected deselected
|
Backspace -> redraw >> handleKeyboard dpy drawFn cancel selected deselected
|
||||||
_ -> return x
|
_ -> return x
|
||||||
isNextOverlayKey keySym = isJust (L.find ((== keySym) . head .chord) selected)
|
isNextOverlayKey keySym = isJust (L.find ((== keySym) . head .chord) selected)
|
||||||
handleNextOverlayKey keySym =
|
handleNextOverlayKey keySym =
|
||||||
case fg of
|
case fg of
|
||||||
[x] -> return $ Selected x
|
[x] -> return $ Selected x
|
||||||
_ -> handleKeyboard dpy drawFn cancel (trim fg) (clear bg) >>= retryBackspace
|
_ -> handleKeyboard dpy drawFn cancel (trim fg) (clear bg) >>= retryBackspace
|
||||||
where
|
where
|
||||||
(fg, bg) = L.partition ((== keySym) . head . chord) selected
|
(fg, bg) = L.partition ((== keySym) . head . chord) selected
|
||||||
trim = map (\o -> o { chord = tail $ chord o })
|
trim = map (\o -> o { chord = tail $ chord o })
|
||||||
clear = map (\o -> o { chord = [] })
|
clear = map (\o -> o { chord = [] })
|
||||||
|
Reference in New Issue
Block a user