{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module XMonad.Config.Arossato
{-# DEPRECATED "This module contains a personal configuration, to be removed from xmonad-contrib. If you use this module, please copy the relevant parts to your configuration or obtain a copy of it on https://xmonad.org/configurations.html and include it as a local module." #-}
(
arossatoConfig
) where
import qualified Data.Map as M
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Actions.CycleWS
import XMonad.Hooks.DynamicLog hiding (xmobar)
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ServerMode
import XMonad.Layout.Accordion
import XMonad.Layout.Magnifier
import XMonad.Layout.NoBorders
import XMonad.Layout.SimpleFloat
import XMonad.Layout.Tabbed
import XMonad.Layout.WindowArranger
import XMonad.Prompt.Shell
import XMonad.Prompt.Ssh
import XMonad.Prompt.Theme
import XMonad.Prompt.Window
import XMonad.Prompt.XMonad
import XMonad.Util.Run
import XMonad.Util.Themes
arossatoConfig :: m (XConfig
(ModifiedLayout
AvoidStruts
(Choose
(ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat)))
(Choose
(ModifiedLayout
WithBorder
(ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest))
(ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion))))))))
arossatoConfig = do
Handle
xmobar <- String -> m Handle
forall (m :: * -> *). MonadIO m => String -> m Handle
spawnPipe String
"xmobar"
XConfig
(ModifiedLayout
AvoidStruts
(Choose
(ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat)))
(Choose
(ModifiedLayout
WithBorder
(ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest))
(ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion)))))))
-> m (XConfig
(ModifiedLayout
AvoidStruts
(Choose
(ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat)))
(Choose
(ModifiedLayout
WithBorder
(ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest))
(ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion))))))))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (XConfig
(ModifiedLayout
AvoidStruts
(Choose
(ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat)))
(Choose
(ModifiedLayout
WithBorder
(ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest))
(ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion)))))))
-> m (XConfig
(ModifiedLayout
AvoidStruts
(Choose
(ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat)))
(Choose
(ModifiedLayout
WithBorder
(ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest))
(ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion)))))))))
-> XConfig
(ModifiedLayout
AvoidStruts
(Choose
(ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat)))
(Choose
(ModifiedLayout
WithBorder
(ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest))
(ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion)))))))
-> m (XConfig
(ModifiedLayout
AvoidStruts
(Choose
(ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat)))
(Choose
(ModifiedLayout
WithBorder
(ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest))
(ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion))))))))
forall a b. (a -> b) -> a -> b
$ XConfig (Choose Tall (Choose (Mirror Tall) Full))
forall a. Default a => a
def
{ workspaces = ["home","var","dev","mail","web","doc"] ++
map show [7 .. 9 :: Int]
, logHook = myDynLog xmobar
, manageHook = newManageHook
, layoutHook = avoidStruts $
decorated |||
noBorders mytabs |||
otherLays
, terminal = "urxvt +sb"
, normalBorderColor = "white"
, focusedBorderColor = "black"
, keys = newKeys
, handleEventHook = serverModeEventHook
, focusFollowsMouse = False
}
where
mytabs :: ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest a
mytabs = DefaultShrinker
-> Theme
-> ModifiedLayout
(Decoration TabbedDecoration DefaultShrinker) Simplest a
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbed DefaultShrinker
shrinkText (ThemeInfo -> Theme
theme ThemeInfo
smallClean)
decorated :: ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat))
a
decorated = DefaultShrinker
-> Theme
-> ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat))
a
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout
(Decoration SimpleDecoration s)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat))
a
simpleFloat' DefaultShrinker
shrinkText (ThemeInfo -> Theme
theme ThemeInfo
smallClean)
tiled :: Tall a
tiled = Int -> Rational -> Rational -> Tall a
forall a. Int -> Rational -> Rational -> Tall a
Tall Int
1 (Rational
3Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
100) (Rational
1Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
2)
otherLays :: ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion)))
Window
otherLays = Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion))
Window
-> ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion)))
Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange (Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion))
Window
-> ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion)))
Window)
-> Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion))
Window
-> ModifiedLayout
WindowArranger
(Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion)))
Window
forall a b. (a -> b) -> a -> b
$
Tall Window -> ModifiedLayout Magnifier Tall Window
forall (l :: * -> *) a. l a -> ModifiedLayout Magnifier l a
magnifier Tall Window
forall {a}. Tall a
tiled ModifiedLayout Magnifier Tall Window
-> Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion)
Window
-> Choose
(ModifiedLayout Magnifier Tall)
(Choose
(ModifiedLayout WithBorder Full) (Choose (Mirror Tall) Accordion))
Window
forall (l :: * -> *) a (r :: * -> *). l a -> r a -> Choose l r a
|||
Full Window -> ModifiedLayout WithBorder Full Window
forall (l :: * -> *).
LayoutClass l Window =>
l Window -> ModifiedLayout WithBorder l Window
noBorders Full Window
forall a. Full a
Full ModifiedLayout WithBorder Full Window
-> Choose (Mirror Tall) Accordion Window
-> Choose
(ModifiedLayout WithBorder Full)
(Choose (Mirror Tall) Accordion)
Window
forall (l :: * -> *) a (r :: * -> *). l a -> r a -> Choose l r a
|||
Tall Window -> Mirror Tall Window
forall (l :: * -> *) a. l a -> Mirror l a
Mirror Tall Window
forall {a}. Tall a
tiled Mirror Tall Window
-> Accordion Window -> Choose (Mirror Tall) Accordion Window
forall (l :: * -> *) a (r :: * -> *). l a -> r a -> Choose l r a
|||
Accordion Window
forall a. Accordion a
Accordion
myManageHook :: Query (Endo (StackSet String l a s sd))
myManageHook = [Query (Endo (StackSet String l a s sd))]
-> Query (Endo (StackSet String l a s sd))
forall m. Monoid m => [m] -> m
composeAll [ Query String
resource Query String -> String -> Query Bool
forall a. Eq a => Query a -> a -> Query Bool
=? String
"win" Query Bool
-> Query (Endo (StackSet String l a s sd))
-> Query (Endo (StackSet String l a s sd))
forall (m :: * -> *) a. (Monad m, Monoid a) => m Bool -> m a -> m a
--> (StackSet String l a s sd -> StackSet String l a s sd)
-> Query (Endo (StackSet String l a s sd))
forall s. (s -> s) -> Query (Endo s)
doF (String -> StackSet String l a s sd -> StackSet String l a s sd
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 String
"doc")
, Query String
resource Query String -> String -> Query Bool
forall a. Eq a => Query a -> a -> Query Bool
=? String
"firefox-bin" Query Bool
-> Query (Endo (StackSet String l a s sd))
-> Query (Endo (StackSet String l a s sd))
forall (m :: * -> *) a. (Monad m, Monoid a) => m Bool -> m a -> m a
--> (StackSet String l a s sd -> StackSet String l a s sd)
-> Query (Endo (StackSet String l a s sd))
forall s. (s -> s) -> Query (Endo s)
doF (String -> StackSet String l a s sd -> StackSet String l a s sd
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 String
"web")
]
newManageHook :: Query (Endo (StackSet String l a s sd))
newManageHook = Query (Endo (StackSet String l a s sd))
forall {a} {s} {l} {sd}.
(Ord a, Eq s) =>
Query (Endo (StackSet String l a s sd))
myManageHook
myDynLog :: Handle -> X ()
myDynLog Handle
h = PP -> X ()
dynamicLogWithPP PP
forall a. Default a => a
def
{ ppCurrent = xmobarColor "yellow" "" . wrap "[" "]"
, ppTitle = xmobarColor "green" "" . shorten 40
, ppVisible = wrap "(" ")"
, ppOutput = hPutStrLn h
}
defKeys :: XConfig Layout -> Map (ButtonMask, Window) (X ())
defKeys = XConfig (Choose Tall (Choose (Mirror Tall) Full))
-> XConfig Layout -> Map (ButtonMask, Window) (X ())
forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (ButtonMask, Window) (X ())
keys XConfig (Choose Tall (Choose (Mirror Tall) Full))
forall a. Default a => a
def
delKeys :: XConfig Layout -> Map (ButtonMask, Window) (X ())
delKeys XConfig Layout
x = ((ButtonMask, Window)
-> Map (ButtonMask, Window) (X ())
-> Map (ButtonMask, Window) (X ()))
-> Map (ButtonMask, Window) (X ())
-> [(ButtonMask, Window)]
-> Map (ButtonMask, Window) (X ())
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ButtonMask, Window)
-> Map (ButtonMask, Window) (X ())
-> Map (ButtonMask, Window) (X ())
forall k a. Ord k => k -> Map k a -> Map k a
M.delete (XConfig Layout -> Map (ButtonMask, Window) (X ())
defKeys XConfig Layout
x) (XConfig Layout -> [(ButtonMask, Window)]
forall {l :: * -> *}. XConfig l -> [(ButtonMask, Window)]
toRemove XConfig Layout
x)
newKeys :: XConfig Layout -> Map (ButtonMask, Window) (X ())
newKeys XConfig Layout
x = (((ButtonMask, Window), X ())
-> Map (ButtonMask, Window) (X ())
-> Map (ButtonMask, Window) (X ()))
-> Map (ButtonMask, Window) (X ())
-> [((ButtonMask, Window), X ())]
-> Map (ButtonMask, Window) (X ())
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (((ButtonMask, Window)
-> X ()
-> Map (ButtonMask, Window) (X ())
-> Map (ButtonMask, Window) (X ()))
-> ((ButtonMask, Window), X ())
-> Map (ButtonMask, Window) (X ())
-> Map (ButtonMask, Window) (X ())
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (ButtonMask, Window)
-> X ()
-> Map (ButtonMask, Window) (X ())
-> Map (ButtonMask, Window) (X ())
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert) (XConfig Layout -> Map (ButtonMask, Window) (X ())
delKeys XConfig Layout
x) (XConfig Layout -> [((ButtonMask, Window), X ())]
forall {l :: * -> *}. XConfig l -> [((ButtonMask, Window), X ())]
toAdd XConfig Layout
x)
toRemove :: XConfig l -> [(ButtonMask, Window)]
toRemove XConfig l
x =
[ (XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_j)
, (XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_k)
, (XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_p)
, (XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_p)
, (XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_q)
, (XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_q)
] [(ButtonMask, Window)]
-> [(ButtonMask, Window)] -> [(ButtonMask, Window)]
forall a. [a] -> [a] -> [a]
++
[(ButtonMask
shiftMask ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x, Window
k) | Window
k <- [Window
xK_1 .. Window
xK_9]]
toAdd :: XConfig l -> [((ButtonMask, Window), X ())]
toAdd XConfig l
x =
[ ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_F12 ), XPConfig -> X ()
xmonadPrompt XPConfig
forall a. Default a => a
def )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_F3 ), XPConfig -> X ()
shellPrompt XPConfig
forall a. Default a => a
def )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_F4 ), XPConfig -> X ()
sshPrompt XPConfig
forall a. Default a => a
def )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_F5 ), XPConfig -> X ()
themePrompt XPConfig
forall a. Default a => a
def )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_F6 ), XPConfig -> WindowPrompt -> XWindowMap -> X ()
windowPrompt XPConfig
forall a. Default a => a
def WindowPrompt
Goto XWindowMap
allWindows )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_F7 ), XPConfig -> WindowPrompt -> XWindowMap -> X ()
windowPrompt XPConfig
forall a. Default a => a
def WindowPrompt
Bring XWindowMap
allWindows )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_comma ), X ()
prevWS )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_period), X ()
nextWS )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_Right ), (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X ()
windows StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.focusDown )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_Left ), (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X ()
windows StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.focusUp )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_F2 ), String -> X ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
"urxvt -fg white -bg black +sb" )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_F4 ), String -> X ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
"~/bin/dict.sh" )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_F5 ), String -> X ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
"~/bin/urlOpen.sh" )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_t ), String -> X ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
"~/bin/teaTime.sh" )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_c ), X ()
kill )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_comma ), IncMasterN -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> IncMasterN
IncMasterN Int
1 ) )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_period), IncMasterN -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> IncMasterN
IncMasterN (-Int
1)) )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_plus ), MagnifyMsg -> X ()
forall a. Message a => a -> X ()
sendMessage MagnifyMsg
MagnifyMore)
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_minus), MagnifyMsg -> X ()
forall a. Message a => a -> X ()
sendMessage MagnifyMsg
MagnifyLess)
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_o ), MagnifyMsg -> X ()
forall a. Message a => a -> X ()
sendMessage MagnifyMsg
ToggleOff )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_o ), MagnifyMsg -> X ()
forall a. Message a => a -> X ()
sendMessage MagnifyMsg
ToggleOn )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_a ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage WindowArrangerMsg
Arrange )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, Window
xK_a ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage WindowArrangerMsg
DeArrange )
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_Left ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
DecreaseLeft Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_Up ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
DecreaseUp Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_Right), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
IncreaseRight Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask , Window
xK_Down ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
IncreaseDown Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask , Window
xK_Left ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
MoveLeft Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask , Window
xK_Right), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
MoveRight Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask , Window
xK_Down ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
MoveDown Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask , Window
xK_Up ), WindowArrangerMsg -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> WindowArrangerMsg
MoveUp Int
10))
, ((XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x , Window
xK_b ), ToggleStruts -> X ()
forall a. Message a => a -> X ()
sendMessage ToggleStruts
ToggleStruts )
] [((ButtonMask, Window), X ())]
-> [((ButtonMask, Window), X ())] -> [((ButtonMask, Window), X ())]
forall a. [a] -> [a] -> [a]
++
[( (ButtonMask
m ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. XConfig l -> ButtonMask
forall (l :: * -> *). XConfig l -> ButtonMask
modMask XConfig l
x, Window
k), (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X ()
windows ((StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X ())
-> (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X ()
forall a b. (a -> b) -> a -> b
$ String
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
f String
i)
| (String
i, Window
k) <- [String] -> [Window] -> [(String, Window)]
forall a b. [a] -> [b] -> [(a, b)]
zip (XConfig l -> [String]
forall (l :: * -> *). XConfig l -> [String]
workspaces XConfig l
x) [Window
xK_1 .. Window
xK_9]
, (String
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
f, ButtonMask
m) <- [(String
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
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, ButtonMask
0), (String
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
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, ButtonMask
shiftMask ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
controlMask)]
]