{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module XMonad.Config.Xfce (
xfceConfig,
desktopLayoutModifiers
) where
import XMonad
import XMonad.Config.Desktop
import qualified Data.Map as M
xfceConfig :: XConfig
(ModifiedLayout
AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))
xfceConfig = XConfig
(ModifiedLayout
AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))
desktopConfig
{ terminal :: String
terminal = String
"xfce4-terminal"
, keys :: XConfig Layout -> Map (ButtonMask, KeySym) (X ())
keys = XConfig Layout -> Map (ButtonMask, KeySym) (X ())
forall (m :: * -> *) (l :: * -> *).
MonadIO m =>
XConfig l -> Map (ButtonMask, KeySym) (m ())
xfceKeys (XConfig Layout -> Map (ButtonMask, KeySym) (X ()))
-> (XConfig Layout -> Map (ButtonMask, KeySym) (X ()))
-> XConfig Layout
-> Map (ButtonMask, KeySym) (X ())
forall m. Monoid m => m -> m -> m
<+> XConfig
(ModifiedLayout
AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))
-> XConfig Layout -> Map (ButtonMask, KeySym) (X ())
forall (l :: * -> *).
XConfig l -> XConfig Layout -> Map (ButtonMask, KeySym) (X ())
keys XConfig
(ModifiedLayout
AvoidStruts (Choose Tall (Choose (Mirror Tall) Full)))
desktopConfig }
xfceKeys :: XConfig l -> Map (ButtonMask, KeySym) (m ())
xfceKeys XConfig{modMask :: forall (l :: * -> *). XConfig l -> ButtonMask
modMask = ButtonMask
modm} = [((ButtonMask, KeySym), m ())] -> Map (ButtonMask, KeySym) (m ())
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ ((ButtonMask
modm, KeySym
xK_p), String -> m ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
"xfrun4")
, ((ButtonMask
modm ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, KeySym
xK_p), String -> m ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
"xfce4-appfinder")
, ((ButtonMask
modm ButtonMask -> ButtonMask -> ButtonMask
forall a. Bits a => a -> a -> a
.|. ButtonMask
shiftMask, KeySym
xK_q), String -> m ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn String
"xfce4-session-logout")
]