aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Prompt/Layout.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Prompt/Layout.hs')
-rw-r--r--XMonad/Prompt/Layout.hs54
1 files changed, 54 insertions, 0 deletions
diff --git a/XMonad/Prompt/Layout.hs b/XMonad/Prompt/Layout.hs
new file mode 100644
index 0000000..6a79a7e
--- /dev/null
+++ b/XMonad/Prompt/Layout.hs
@@ -0,0 +1,54 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Prompt.Layout
+-- Copyright : (C) 2007 Andrea Rossato, David Roundy
+-- License : BSD3
+--
+-- Maintainer : droundy@darcs.net
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A layout-selection prompt for XMonad
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Prompt.Layout (
+ -- * Usage
+ -- $usage
+ layoutPrompt
+ ) where
+
+import Control.Monad.State ( gets )
+import Data.List ( sort, nub )
+import XMonad hiding ( workspaces )
+import XMonad.Operations ( sendMessage )
+import XMonad.Prompt
+import XMonad.StackSet ( workspaces, layout )
+import XMonad.Layout.LayoutCombinators ( JumpToLayout(..) )
+
+-- $usage
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonad.Prompt.Layout
+--
+-- > , ((modMask .|. shiftMask, xK_m ), layoutPrompt defaultXPConfig)
+
+-- WARNING: This prompt won't display all possible layouts, because the
+-- code to enable this was rejected from xmonad core. It only displays
+-- layouts that are actually in use. Also, you can only select layouts if
+-- you are using NewSelect, rather than the Select defined in xmonad core
+-- (which doesn't have this feature). So all in all, this module is really
+-- more a proof-of-principle than something you can actually use
+-- productively.
+
+data Wor = Wor String
+
+instance XPrompt Wor where
+ showXPrompt (Wor x) = x
+
+layoutPrompt :: XPConfig -> X ()
+layoutPrompt c = do ls <- gets (map (description . layout) . workspaces . windowset)
+ mkXPrompt (Wor "") c (mkCompl $ sort $ nub ls) (sendMessage . JumpToLayout)
+
+mkCompl :: [String] -> String -> IO [String]
+mkCompl l s = return $ filter (\x -> take (length s) x == s) l