[XMonad] Reindent a bunch of definitions

This commit is contained in:
Ivan Malison 2016-11-25 18:48:14 -08:00
parent fa7c46b764
commit 6d17f96ecf
No known key found for this signature in database
GPG Key ID: 62530EFBE99DC2F8

View File

@ -49,18 +49,20 @@ import XMonad.Util.NamedScratchpad
(NamedScratchpad(NS), nonFloating, namedScratchpadAction) (NamedScratchpad(NS), nonFloating, namedScratchpadAction)
import XMonad.Util.NamedWindows (getName) import XMonad.Util.NamedWindows (getName)
main = xmonad $ def main =
{ modMask = mod4Mask xmonad $ def
, terminal = "urxvt" { modMask = mod4Mask
, manageHook = manageDocks <+> myManageHook <+> manageHook def , terminal = "urxvt"
, layoutHook = myLayoutHook , manageHook = manageDocks <+> myManageHook <+> manageHook def
, logHook = toggleFadeInactiveLogHook 0.9 +++ ewmhWorkspaceNamesLogHook , layoutHook = myLayoutHook
, handleEventHook = docksEventHook <+> fullscreenEventHook +++ , logHook = toggleFadeInactiveLogHook 0.9 +++ ewmhWorkspaceNamesLogHook
ewmhDesktopsEventHook +++ pagerHintsEventHook +++ , handleEventHook =
followIfNoMagicFocus docksEventHook <+> fullscreenEventHook +++
, startupHook = myStartup +++ ewmhWorkspaceNamesLogHook ewmhDesktopsEventHook +++ pagerHintsEventHook +++ followIfNoMagicFocus
, keys = customKeys (const []) addKeys , startupHook = myStartup +++ ewmhWorkspaceNamesLogHook
} where , keys = customKeys (const []) addKeys
}
where
x +++ y = mappend y x x +++ y = mappend y x
@ -127,18 +129,19 @@ myStartup = spawn "systemctl --user start wm.target"
-- Manage hook -- Manage hook
myManageHook = composeAll . concat $ myManageHook =
[ [ transmissionSelector --> doShift "5" ] composeAll . concat $
-- Hangouts being on a separate workspace freezes chrome [ [transmissionSelector --> doShift "5"]
-- , [ hangoutsSelector --> doShift "2"] -- Hangouts being on a separate workspace freezes chrome
] -- , [ hangoutsSelector --> doShift "2"]
]
-- Toggles -- Toggles
unmodifyLayout (ModifiedLayout _ x') = x' unmodifyLayout (ModifiedLayout _ x') = x'
selectLimit = DM.menuArgs "rofi" ["-dmenu", "-i"] ["2", "3", "4"] >>= selectLimit =
(setLimit . read) DM.menuArgs "rofi" ["-dmenu", "-i"] ["2", "3", "4"] >>= (setLimit . read)
data MyToggles = LIMIT data MyToggles = LIMIT
| GAPS | GAPS
@ -146,34 +149,37 @@ data MyToggles = LIMIT
deriving (Read, Show, Eq, Typeable) deriving (Read, Show, Eq, Typeable)
instance Transformer MyToggles Window where instance Transformer MyToggles Window where
transform LIMIT x k = k (limitSlice 2 x) unmodifyLayout transform LIMIT x k = k (limitSlice 2 x) unmodifyLayout
transform GAPS x k = k (smartSpacing 5 x) unmodifyLayout transform GAPS x k = k (smartSpacing 5 x) unmodifyLayout
transform MAGICFOCUS x k = k (magicFocus x) unmodifyLayout transform MAGICFOCUS x k = k (magicFocus x) unmodifyLayout
myToggles = [LIMIT, GAPS, MAGICFOCUS] myToggles = [LIMIT, GAPS, MAGICFOCUS]
otherToggles = [NBFULL, MIRROR] otherToggles = [NBFULL, MIRROR]
followIfNoMagicFocus = followOnlyIf $ fmap (fromMaybe False . fmap not) $ followIfNoMagicFocus =
isToggleActive MAGICFOCUS followOnlyIf $ maybe False not <$> isToggleActive MAGICFOCUS
togglesMap = fmap M.fromList $ sequence $ togglesMap =
map toggleTuple myToggles ++ map toggleTuple otherToggles fmap M.fromList $ sequence $
where map toggleTuple myToggles ++ map toggleTuple otherToggles
toggleTuple toggle = fmap (\str -> (str, Toggle toggle)) where
(toggleToStringWithState toggle) toggleTuple toggle =
fmap (\str -> (str, Toggle toggle)) (toggleToStringWithState toggle)
toggleStateToString s = case s of
Just True -> "ON" toggleStateToString s =
Just False -> "OFF" case s of
Nothing -> "N/A" Just True -> "ON"
Just False -> "OFF"
Nothing -> "N/A"
toggleToStringWithState :: (Transformer t Window, Show t) => t -> X String toggleToStringWithState :: (Transformer t Window, Show t) => t -> X String
toggleToStringWithState toggle = toggleToStringWithState toggle =
(printf "%s (%s)" (show toggle) . toggleStateToString) <$> (printf "%s (%s)" (show toggle) . toggleStateToString) <$> isToggleActive toggle
isToggleActive toggle
selectToggle = togglesMap >>= DM.menuMapArgs "rofi" ["-dmenu", "-i"] >>= selectToggle =
flip whenJust sendMessage togglesMap >>= DM.menuMapArgs "rofi" ["-dmenu", "-i"] >>=
flip whenJust sendMessage
toggleInState :: (Transformer t Window) => t -> Maybe Bool -> X Bool toggleInState :: (Transformer t Window) => t -> Maybe Bool -> X Bool
toggleInState t s = fmap (/= s) (isToggleActive t) toggleInState t s = fmap (/= s) (isToggleActive t)
@ -188,8 +194,8 @@ setToggleActive = (void .) . setToggleActive'
deactivateFull = setToggleActive NBFULL False deactivateFull = setToggleActive NBFULL False
toggleOr toggle toState action = setToggleActive' toggle toState >>= toggleOr toggle toState action =
((`when` action) . not) setToggleActive' toggle toState >>= ((`when` action) . not)
deactivateFullOr = toggleOr NBFULL False deactivateFullOr = toggleOr NBFULL False
deactivateFullAnd action = sequence_ [deactivateFull, action] deactivateFullAnd action = sequence_ [deactivateFull, action]
@ -206,22 +212,25 @@ layoutsStart layout = (layout, [Layout layout])
(|||!) (joined, layouts) newLayout = (|||!) (joined, layouts) newLayout =
(joined ||| newLayout, layouts ++ [Layout newLayout]) (joined ||| newLayout, layouts ++ [Layout newLayout])
layoutInfo = layoutsStart (rename "Columns" $ multiCol [1, 1] 2 0.01 (-0.5)) |||! layoutInfo =
rename "Large Main" (Tall 1 (3/100) (3/4)) |||! layoutsStart (rename "Columns" $ multiCol [1, 1] 2 0.01 (-0.5)) |||!
rename "2 Columns" (Tall 1 (3/100) (1/2)) |||! rename "Large Main" (Tall 1 (3 / 100) (3 / 4)) |||!
Accordion rename "2 Columns" (Tall 1 (3 / 100) (1 / 2)) |||!
Accordion
layoutList = snd layoutInfo layoutList = snd layoutInfo
layoutNames = [description layout | layout <- layoutList] layoutNames = [description layout | layout <- layoutList]
selectLayout = DM.menuArgs "rofi" ["-dmenu", "-i"] layoutNames >>= selectLayout =
(sendMessage . JumpToLayout) DM.menuArgs "rofi" ["-dmenu", "-i"] layoutNames >>=
(sendMessage . JumpToLayout)
myLayoutHook = avoidStruts . minimize . boringAuto . mkToggle1 MIRROR .
mkToggle1 LIMIT . mkToggle1 GAPS . mkToggle1 MAGICFOCUS . myLayoutHook =
mkToggle1 NBFULL . workspaceNamesHook . smartBorders . noBorders $ avoidStruts . minimize . boringAuto . mkToggle1 MIRROR . mkToggle1 LIMIT .
fst layoutInfo mkToggle1 GAPS . mkToggle1 MAGICFOCUS . mkToggle1 NBFULL . workspaceNamesHook .
smartBorders . noBorders $ fst layoutInfo
-- WindowBringer -- WindowBringer
@ -298,7 +307,7 @@ ewmhWorkspaceNamesLogHook = do
ewmhDesktopsLogHookCustom id tagRemapping ewmhDesktopsLogHookCustom id tagRemapping
getWorkspaceNameFromTag getWSName tag = getWorkspaceNameFromTag getWSName tag =
printf "%s: %s " tag (fromMaybe "(Empty)" (getWSName tag)) printf "%s: %s " tag (fromMaybe "(Empty)" (getWSName tag))
-- Toggleable fade -- Toggleable fade
@ -334,9 +343,9 @@ getCurrentWS = W.stack . W.workspace . W.current
withWorkspace f = withWindowSet $ \ws -> maybe (return ()) f (getCurrentWS ws) withWorkspace f = withWindowSet $ \ws -> maybe (return ()) f (getCurrentWS ws)
minimizeOtherClassesInWorkspace = minimizeOtherClassesInWorkspace =
actOnWindowsInWorkspace minimizeWindow windowsWithUnfocusedClass actOnWindowsInWorkspace minimizeWindow windowsWithUnfocusedClass
maximizeSameClassesInWorkspace = maximizeSameClassesInWorkspace =
actOnWindowsInWorkspace maybeUnminimize windowsWithFocusedClass actOnWindowsInWorkspace maybeUnminimize windowsWithFocusedClass
-- Type annotation is needed to resolve ambiguity -- Type annotation is needed to resolve ambiguity
actOnWindowsInWorkspace :: (Window -> X ()) -> (W.Stack Window -> X [Window]) -> X () actOnWindowsInWorkspace :: (Window -> X ()) -> (W.Stack Window -> X [Window]) -> X ()
@ -349,13 +358,13 @@ windowsWithOtherClasses = windowsMatchingPredicate (/=)
windowsWithSameClass = windowsMatchingPredicate (==) windowsWithSameClass = windowsMatchingPredicate (==)
windowsMatchingPredicate predicate window workspace = windowsMatchingPredicate predicate window workspace =
windowsSatisfyingPredicate workspace $ do windowsSatisfyingPredicate workspace $ do
windowClass <- getClass window windowClass <- getClass window
return $ predicate windowClass return $ predicate windowClass
windowsSatisfyingPredicate workspace getPredicate = do windowsSatisfyingPredicate workspace getPredicate = do
predicate <- getPredicate predicate <- getPredicate
filterM (\w -> predicate <$> getClass w) (W.integrate workspace) filterM (\w -> predicate <$> getClass w) (W.integrate workspace)
windowIsMinimized w = do windowIsMinimized w = do
minimized <- XS.gets minimizedStack minimized <- XS.gets minimizedStack
@ -379,26 +388,29 @@ restoreOrMinimizeOtherClasses = withLastMinimized' $
-- Use greedyView to switch to the correct workspace, and then focus on the -- Use greedyView to switch to the correct workspace, and then focus on the
-- appropriate window within that workspace. -- appropriate window within that workspace.
greedyFocusWindow w ws = W.focusWindow w $ W.greedyView greedyFocusWindow w ws =
(fromMaybe (W.currentTag ws) $ W.findTag w ws) ws W.focusWindow w $
W.greedyView (fromMaybe (W.currentTag ws) $ W.findTag w ws) ws
shiftThenView i = W.greedyView i . W.shift i shiftThenView i = W.greedyView i . W.shift i
shiftToEmptyAndView = doTo Next EmptyWS DWO.getSortByOrder (windows . shiftThenView)
greedyBringWindow w = greedyFocusWindow w . bringWindow w greedyBringWindow w = greedyFocusWindow w . bringWindow w
shiftToEmptyAndView =
doTo Next EmptyWS DWO.getSortByOrder (windows . shiftThenView)
swapFocusedWith w ws = W.modify' (swapFocusedWith' w) (W.delete' w ws) swapFocusedWith w ws = W.modify' (swapFocusedWith' w) (W.delete' w ws)
swapFocusedWith' w (W.Stack current ls rs) = W.Stack w ls (rs ++ [current]) swapFocusedWith' w (W.Stack current ls rs) = W.Stack w ls (rs ++ [current])
swapMinimizeStateAfter action = withFocused $ \originalWindow -> do swapMinimizeStateAfter action =
_ <- action withFocused $
restoreFocus $ do \originalWindow -> do
maybeUnminimizeFocused _ <- action
withFocused $ \newWindow -> restoreFocus $
when (newWindow /= originalWindow) do maybeUnminimizeFocused
$ minimizeWindow originalWindow withFocused $
\newWindow -> when (newWindow /= originalWindow) $ minimizeWindow originalWindow
-- Named Scratchpads -- Named Scratchpads