diff options
author | Spencer Janssen <sjanssen@cse.unl.edu> | 2007-09-25 23:49:12 +0200 |
---|---|---|
committer | Spencer Janssen <sjanssen@cse.unl.edu> | 2007-09-25 23:49:12 +0200 |
commit | caf72acbee02a7e9679c74c7af747cbb7d5755a7 (patch) | |
tree | f13a712c228c6565bc484778c515fe185d346f40 | |
parent | ec697eed5aebecb065ff7f15345ad21965225e1e (diff) | |
download | XMonadContrib-caf72acbee02a7e9679c74c7af747cbb7d5755a7.tar.gz XMonadContrib-caf72acbee02a7e9679c74c7af747cbb7d5755a7.tar.xz XMonadContrib-caf72acbee02a7e9679c74c7af747cbb7d5755a7.zip |
Remove LayoutChoice, this functionality is in the core
darcs-hash:20070925214912-a5988-27e438ff11847286eaf91fcb069f79a7d5073274.gz
-rw-r--r-- | LayoutChoice.hs | 62 | ||||
-rw-r--r-- | MetaModule.hs | 1 |
2 files changed, 0 insertions, 63 deletions
diff --git a/LayoutChoice.hs b/LayoutChoice.hs deleted file mode 100644 index 30f48d7..0000000 --- a/LayoutChoice.hs +++ /dev/null @@ -1,62 +0,0 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} ------------------------------------------------------------------------------ --- | --- Module : XMonadContrib.LayoutChoice --- Copyright : (c) David Roundy --- License : BSD-style (see xmonad/LICENSE) --- --- Maintainer : droundy@darcs.net --- Stability : unstable --- Portability : unportable --- --- A replacement for the default layout handling. --- ------------------------------------------------------------------------------ - -module XMonadContrib.LayoutChoice ( - -- * Usage: - -- $usage - layoutChoice - , ChangeLayout(..) - ) where - -import Data.List ( partition ) -import Data.Maybe ( fromMaybe ) -import XMonad -import Operations ( tall, UnDoLayout(..) ) - --- $usage --- You can use this module to replace the default layout handling of --- xmonad. See the docstring docs for example usage. - --- %import XMonadContrib.LayoutChoice --- %layout , layoutChoice [("full", full), --- %layout ("tall", tall 1 0.03 0.5)] - --- %keybind , ((modMask, xK_space), sendMessage NextLayout) --- %keybind , ((modMask .|. shiftMask, xK_space), sendMessage PrevLayout) --- %keybind , ((modMask, xK_f), sendMessage (JumpToLayout "full")) - -data ChangeLayout = NextLayout | PrevLayout | JumpToLayout String - deriving ( Eq, Show, Typeable ) -instance Message ChangeLayout - -layoutChoice :: [(String, Layout a)] -> Layout a -layoutChoice [] = tall 1 0.03 0.5 -layoutChoice ((n,l):ls) = Layout { doLayout = dolay - , modifyLayout = md } - where dolay r s = do (x,ml') <- doLayout l r s - return (x, (\l' -> layoutChoice ((n,l'):ls)) `fmap` ml') - md m | Just NextLayout <- fromMessage m = switchl rls - | Just PrevLayout <- fromMessage m = switchl rls' - | Just (JumpToLayout x) <- fromMessage m = switchl (j x) - | otherwise = do ml' <- modifyLayout l m - return $ (\l' -> layoutChoice ((n,l'):ls)) `fmap` ml' - - rls (x:xs) = xs ++ [x] - rls [] = [] - rls' = reverse . rls . reverse - j s zs = case partition (\z -> s == fst z) zs of - (xs,ys) -> xs++ys - switchl f = do ml' <- modifyLayout l (SomeMessage UnDoLayout) - return $ Just (layoutChoice $ f $ (n,fromMaybe l ml'):ls) diff --git a/MetaModule.hs b/MetaModule.hs index 070292b..cc40fe6 100644 --- a/MetaModule.hs +++ b/MetaModule.hs @@ -41,7 +41,6 @@ import XMonadContrib.FlexibleManipulate () import XMonadContrib.FloatKeys () import XMonadContrib.FocusNth () import XMonadContrib.HintedTile () -import XMonadContrib.LayoutChoice () import XMonadContrib.LayoutModifier () import XMonadContrib.LayoutHints () import XMonadContrib.LayoutScreens () |