aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Named.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-11-11 20:50:36 +0100
committerDavid Roundy <droundy@darcs.net>2007-11-11 20:50:36 +0100
commitf6a589c128a45ec862b704ba5d02a7bc91deae2b (patch)
tree4e8eeb3822b4bc879f074ab83f81912d405fff0f /XMonad/Layout/Named.hs
parent3352241c8cfe40428742ca6829ea427498f949e5 (diff)
downloadXMonadContrib-f6a589c128a45ec862b704ba5d02a7bc91deae2b.tar.gz
XMonadContrib-f6a589c128a45ec862b704ba5d02a7bc91deae2b.tar.xz
XMonadContrib-f6a589c128a45ec862b704ba5d02a7bc91deae2b.zip
add two new modules, one to name layouts, another to select a layout.
The latter is pretty useless, as there's no way to find out what layouts are available, but it can at least allow you to select between any layouts that you happen to be using already (in one workspace or another). The former is handy any time you'd rather have a short name for a layout (either for selecting, or for viewing in a status bar). darcs-hash:20071111195036-72aca-8ffbd496a9dbbdd7ca7e92a5bbedb568b2384485.gz
Diffstat (limited to 'XMonad/Layout/Named.hs')
-rw-r--r--XMonad/Layout/Named.hs39
1 files changed, 39 insertions, 0 deletions
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