aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Fullscreen.hs
diff options
context:
space:
mode:
authorDevin Mullins <devinmullins@gmail.com>2014-09-14 08:48:28 +0200
committerDevin Mullins <devinmullins@gmail.com>2014-09-14 08:48:28 +0200
commit0e15f95573b46f5cd0ffe8c701de1bb72aae15ff (patch)
tree0ba0ce375f7ff1564335daf8a1607da93451c34c /XMonad/Layout/Fullscreen.hs
parent3fa72e4522e05c0d55c55d396f37d971153540be (diff)
downloadXMonadContrib-0e15f95573b46f5cd0ffe8c701de1bb72aae15ff.tar.gz
XMonadContrib-0e15f95573b46f5cd0ffe8c701de1bb72aae15ff.tar.xz
XMonadContrib-0e15f95573b46f5cd0ffe8c701de1bb72aae15ff.zip
XMonad.Config.Prime, a do-notation for config
Ignore-this: f7397aa6e6efe5d76acebfa22c567baa Note that the use of RebindableSyntax is because of the need to vary the layoutHook type throughout the config. The alternative, using the existential Layout type, was rejected because it required TemplateHaskell in order to look nice, and TemplateHaskell is not portable. I've tried to make a version of (>>) that also worked on normal monads, but have had no luck as of yet. Maybe some intrepid soul can add it later. darcs-hash:20140914064828-c7120-fbf2746080bb2410b2b70da290fd50eefd49435d.gz
Diffstat (limited to '')
-rw-r--r--XMonad/Layout/Fullscreen.hs19
1 files changed, 17 insertions, 2 deletions
diff --git a/XMonad/Layout/Fullscreen.hs b/XMonad/Layout/Fullscreen.hs
index 386baab..779a1e9 100644
--- a/XMonad/Layout/Fullscreen.hs
+++ b/XMonad/Layout/Fullscreen.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances #-}
+{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.Fullscreen
@@ -15,7 +15,8 @@
module XMonad.Layout.Fullscreen
( -- * Usage:
-- $usage
- fullscreenFull
+ fullscreenSupport
+ ,fullscreenFull
,fullscreenFocus
,fullscreenFullRect
,fullscreenFocusRect
@@ -63,6 +64,20 @@ import Control.Arrow (second)
-- > myLayouts = fullscreenFull someLayout
--
+-- | Modifies your config to apply basic fullscreen support -- fullscreen
+-- windows when they request it. Example usage:
+--
+-- > main = xmonad
+-- > $ fullscreenSupport
+-- > $ defaultConfig { ... }
+fullscreenSupport :: LayoutClass l Window =>
+ XConfig l -> XConfig (ModifiedLayout FullscreenFull l)
+fullscreenSupport c = c {
+ layoutHook = fullscreenFull $ layoutHook c,
+ handleEventHook = handleEventHook c <+> fullscreenEventHook,
+ manageHook = manageHook c <+> fullscreenManageHook
+ }
+
-- | Messages that control the fullscreen state of the window.
-- AddFullscreen and RemoveFullscreen are sent to all layouts
-- when a window wants or no longer wants to be fullscreen.