aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--XMonad/Config/Droundy.hs7
-rw-r--r--XMonad/Layout/Named.hs39
-rw-r--r--XMonad/Prompt/Layout.hs54
-rw-r--r--XMonadContrib.cabal2
4 files changed, 100 insertions, 2 deletions
diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs
index 95d10e1..8004a9d 100644
--- a/XMonad/Config/Droundy.hs
+++ b/XMonad/Config/Droundy.hs
@@ -34,6 +34,7 @@ import Graphics.X11.Xlib
import XMonad.Layout.Tabbed
import XMonad.Layout.Combo
+import XMonad.Layout.Named
import XMonad.Layout.LayoutCombinators
import XMonad.Layout.Square
import XMonad.Layout.LayoutScreens
@@ -43,6 +44,7 @@ import XMonad.Layout.WorkspaceDir
import XMonad.Layout.ToggleLayouts
import XMonad.Prompt
+import XMonad.Prompt.Layout
import XMonad.Prompt.Shell
import XMonad.Actions.CopyWindow
@@ -112,6 +114,7 @@ keys x = M.fromList $
, ((modMask x, xK_m ), withWorkspace myXPConfig (windows . W.shift))
, ((modMask x .|. shiftMask, xK_m ), withWorkspace myXPConfig (windows . copy))
, ((modMask x .|. shiftMask, xK_r), renameWorkspace myXPConfig)
+ , ((modMask x, xK_l ), layoutPrompt myXPConfig)
, ((modMask x .|. controlMask, xK_space), sendMessage ToggleLayout)
]
@@ -138,8 +141,8 @@ config = defaultConfig
{ borderWidth = 1 -- Width of the window border in pixels.
, XMonad.workspaces = ["1:mutt","2:iceweasel"]
, layoutHook = Layout $ workspaceDir "~" $ windowNavigation $ toggleLayouts (noBorders Full) $
- noBorders mytab |||
- mytab <-/> combineTwo Square mytab mytab |||
+ Named "tabbed" (noBorders mytab) |||
+ Named "xclock" (mytab <-/> combineTwo Square mytab mytab) |||
mytab <//> mytab
, terminal = "xterm" -- The preferred terminal program.
, normalBorderColor = "#dddddd" -- Border color for unfocused windows.
diff --git a/XMonad/Layout/Named.hs b/XMonad/Layout/Named.hs
new file mode 100644
index 0000000..54ef89b
--- /dev/null
+++ b/XMonad/Layout/Named.hs
@@ -0,0 +1,39 @@
+{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Named
+-- Copyright : (c) David Roundy <droundy@darcs.net>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : David Roundy <droundy@darcs.net>
+-- Stability : unstable
+-- Portability : unportable
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Named (
+ -- * Usage
+ -- $usage
+ Named(Named)
+ ) where
+
+import XMonad
+
+-- $usage
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonad.Layout.Named
+--
+-- and change the name of a given layout by
+--
+-- > layout = Named "real big" Full ||| ...
+
+data Named l a = Named String (l a) deriving ( Read, Show )
+
+instance (LayoutClass l a) => LayoutClass (Named l) a where
+ doLayout (Named n l) r s = do (ws, ml') <- doLayout l r s
+ return (ws, Named n `fmap` ml')
+ handleMessage (Named n l) mess = do ml' <- handleMessage l mess
+ return $ Named n `fmap` ml'
+ description (Named n _) = n
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
diff --git a/XMonadContrib.cabal b/XMonadContrib.cabal
index 65b69c8..dc3b0a1 100644
--- a/XMonadContrib.cabal
+++ b/XMonadContrib.cabal
@@ -76,6 +76,7 @@ library
XMonad.Layout.MosaicAlt
-- XMonad.Layout.Mosaic
XMonad.Layout.MultiToggle
+ XMonad.Layout.Named
XMonad.Layout.NoBorders
XMonad.Layout.ResizableTile
XMonad.Layout.Roledex
@@ -90,6 +91,7 @@ library
XMonad.Layout.WorkspaceDir
XMonad.Prompt.Directory
XMonad.Prompt
+ XMonad.Prompt.Layout
XMonad.Prompt.Man
XMonad.Prompt.Shell
XMonad.Prompt.Ssh