{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module XMonad.Config.Bepo (
bepoConfig, bepoKeys
) where
import XMonad
import qualified XMonad.StackSet as W
import qualified Data.Map as M
bepoConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
bepoConfig = XConfig (Choose Tall (Choose (Mirror Tall) Full))
forall a. Default a => a
def { keys :: XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys = XConfig Layout -> Map (KeyMask, KeySym) (X ())
forall {l :: * -> *}. XConfig l -> Map (KeyMask, KeySym) (X ())
bepoKeys (XConfig Layout -> Map (KeyMask, KeySym) (X ()))
-> (XConfig Layout -> Map (KeyMask, KeySym) (X ()))
-> XConfig Layout
-> Map (KeyMask, KeySym) (X ())
forall a. Semigroup a => a -> a -> a
<> XConfig (Choose Tall (Choose (Mirror Tall) Full))
-> XConfig Layout -> Map (KeyMask, KeySym) (X ())
forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
keys XConfig (Choose Tall (Choose (Mirror Tall) Full))
forall a. Default a => a
def }
bepoKeys :: XConfig l -> Map (KeyMask, KeySym) (X ())
bepoKeys conf :: XConfig l
conf@XConfig { modMask :: forall (l :: * -> *). XConfig l -> KeyMask
modMask = KeyMask
modm } = [((KeyMask, KeySym), X ())] -> Map (KeyMask, KeySym) (X ())
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([((KeyMask, KeySym), X ())] -> Map (KeyMask, KeySym) (X ()))
-> [((KeyMask, KeySym), X ())] -> Map (KeyMask, KeySym) (X ())
forall a b. (a -> b) -> a -> b
$
((KeyMask
modm, KeySym
xK_semicolon), IncMasterN -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> IncMasterN
IncMasterN (-Int
1)))
((KeyMask, KeySym), X ())
-> [((KeyMask, KeySym), X ())] -> [((KeyMask, KeySym), X ())]
forall a. a -> [a] -> [a]
: [((KeyMask
m KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
modm, KeySym
k), (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WindowSet -> WindowSet) -> X ()
forall a b. (a -> b) -> a -> b
$ String -> WindowSet -> WindowSet
f String
i)
| (String
i, KeySym
k) <- [String] -> [KeySym] -> [(String, KeySym)]
forall a b. [a] -> [b] -> [(a, b)]
zip (XConfig l -> [String]
forall (l :: * -> *). XConfig l -> [String]
workspaces XConfig l
conf) [KeySym
0x22,KeySym
0xab,KeySym
0xbb,KeySym
0x28,KeySym
0x29,KeySym
0x40,KeySym
0x2b,KeySym
0x2d,KeySym
0x2f,KeySym
0x2a],
(String -> WindowSet -> WindowSet
f, KeyMask
m) <- [(String -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
W.greedyView, KeyMask
0), (String -> WindowSet -> WindowSet
forall a s i l sd.
(Ord a, Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
W.shift, KeyMask
shiftMask)]]