module XMonad.Actions.PerLayoutKeys (
chooseActionByLayout,
bindByLayout
) where
import XMonad
import XMonad.StackSet as S
chooseActionByLayout :: (String->X()) -> X()
chooseActionByLayout :: (String -> X ()) -> X ()
chooseActionByLayout String -> X ()
f = (WindowSet -> X ()) -> X ()
forall a. (WindowSet -> X a) -> X a
withWindowSet (String -> X ()
f (String -> X ()) -> (WindowSet -> String) -> WindowSet -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Layout Window -> String
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> String
description (Layout Window -> String)
-> (WindowSet -> Layout Window) -> WindowSet -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Workspace String (Layout Window) Window -> Layout Window
forall i l a. Workspace i l a -> l
S.layout(Workspace String (Layout Window) Window -> Layout Window)
-> (WindowSet -> Workspace String (Layout Window) Window)
-> WindowSet
-> Layout Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
S.workspace (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window)
-> (WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> WindowSet
-> Workspace String (Layout Window) Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
S.current)
bindByLayout :: [(String, X())] -> X()
bindByLayout :: [(String, X ())] -> X ()
bindByLayout [(String, X ())]
bindings = (String -> X ()) -> X ()
chooseActionByLayout String -> X ()
chooser where
chooser :: String -> X ()
chooser String
l = case String -> [(String, X ())] -> Maybe (X ())
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
l [(String, X ())]
bindings of
Just X ()
action -> X ()
action
Maybe (X ())
Nothing -> case String -> [(String, X ())] -> Maybe (X ())
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"" [(String, X ())]
bindings of
Just X ()
action -> X ()
action
Maybe (X ())
Nothing -> () -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()