aboutsummaryrefslogtreecommitdiffstats
path: root/ToggleLayouts.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-10-18 23:45:25 +0200
committerDavid Roundy <droundy@darcs.net>2007-10-18 23:45:25 +0200
commitbeb5ef55e3daccdc2d399c17912b025d9a424875 (patch)
tree208d3727f22b87a8bca21a09e40f8b8c7c8f6050 /ToggleLayouts.hs
parent980b7178e7c1aac51d70003cc5d5ce4168f51715 (diff)
downloadXMonadContrib-beb5ef55e3daccdc2d399c17912b025d9a424875.tar.gz
XMonadContrib-beb5ef55e3daccdc2d399c17912b025d9a424875.tar.xz
XMonadContrib-beb5ef55e3daccdc2d399c17912b025d9a424875.zip
add ToggleLayouts module.
darcs-hash:20071018214525-72aca-7364a52e0146efcd8f6fd81026f21540f20c1205.gz
Diffstat (limited to 'ToggleLayouts.hs')
-rw-r--r--ToggleLayouts.hs67
1 files changed, 67 insertions, 0 deletions
diff --git a/ToggleLayouts.hs b/ToggleLayouts.hs
new file mode 100644
index 0000000..60b510b
--- /dev/null
+++ b/ToggleLayouts.hs
@@ -0,0 +1,67 @@
+{-# -fglasgow-exts #-} -- For deriving Data/Typeable
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonadContrib.ToggleLayouts
+-- Copyright : (c) David Roundy <droundy@darcs.net>
+-- License : BSD
+--
+-- Maintainer : David Roundy <droundy@darcs.net>
+-- Stability : unstable
+-- Portability : portable
+--
+-- A module for writing easy Layouts
+-----------------------------------------------------------------------------
+
+module XMonadContrib.ToggleLayouts (
+ -- * Usage
+ -- $usage
+ toggleLayouts, ToggleLayout(..)
+ ) where
+
+import XMonad
+import Operations ( LayoutMessages(Hide, ReleaseResources) )
+
+-- $usage
+-- Use toggleLayouts to toggle between two layouts.
+-- import XMonadContrib.ToggleLayouts, and add to your layoutHook something like
+-- > layoutHook = Layout $ toggleLayouts (noBorders Full) $ Select layouts
+-- and a key binding like
+-- > , ((modMask .|. controlMask, xK_space), sendMessage ToggleLayout)
+
+data ToggleLayouts lt lf a = ToggleLayouts Bool (lt a) (lf a) deriving (Read,Show)
+data ToggleLayout = ToggleLayout deriving (Read,Show,Typeable)
+instance Message ToggleLayout
+
+toggleLayouts :: (LayoutClass lt a, LayoutClass lf a) => lt a -> lf a -> ToggleLayouts lt lf a
+toggleLayouts = ToggleLayouts False
+
+instance (LayoutClass lt a, LayoutClass lf a) => LayoutClass (ToggleLayouts lt lf) a where
+ doLayout (ToggleLayouts True lt lf) r s = do (ws,mlt') <- doLayout lt r s
+ return (ws,fmap (\lt' -> ToggleLayouts True lt' lf) mlt')
+ doLayout (ToggleLayouts False lt lf) r s = do (ws,mlf') <- doLayout lf r s
+ return (ws,fmap (\lf' -> ToggleLayouts False lt lf') mlf')
+ description (ToggleLayouts True lt _) = description lt
+ description (ToggleLayouts False _ lf) = description lf
+ handleMessage (ToggleLayouts bool lt lf) m
+ | Just ReleaseResources <- fromMessage m =
+ do mlf' <- handleMessage lf m
+ mlt' <- handleMessage lt m
+ return $ case (mlt',mlf') of
+ (Nothing ,Nothing ) -> Nothing
+ (Just lt',Nothing ) -> Just $ ToggleLayouts bool lt' lf
+ (Nothing ,Just lf') -> Just $ ToggleLayouts bool lt lf'
+ (Just lt',Just lf') -> Just $ ToggleLayouts bool lt' lf'
+ handleMessage (ToggleLayouts True lt lf) m
+ | Just ToggleLayout <- fromMessage m = do mlt' <- handleMessage lt (SomeMessage Hide)
+ let lt' = maybe lt id mlt'
+ return $ Just $ ToggleLayouts False lt' lf
+ | otherwise = do mlt' <- handleMessage lt m
+ return $ fmap (\lt' -> ToggleLayouts True lt' lf) mlt'
+ handleMessage (ToggleLayouts False lt lf) m
+ | Just ToggleLayout <- fromMessage m = do mlf' <- handleMessage lf (SomeMessage Hide)
+ let lf' = maybe lf id mlf'
+ return $ Just $ ToggleLayouts True lt lf'
+ | otherwise = do mlf' <- handleMessage lf m
+ return $ fmap (\lf' -> ToggleLayouts False lt lf') mlf'