aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Named.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-01-28 17:13:43 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-01-28 17:13:43 +0100
commit10126d6a3de14c93ee13f646e7ede0a6cc14871d (patch)
tree4e6222ce47f3789009bfdbe7cd85897fe137ca17 /XMonad/Layout/Named.hs
parent03e5ae0446142c78b6c26e9b0e1ac76fb1dcbc97 (diff)
downloadXMonadContrib-10126d6a3de14c93ee13f646e7ede0a6cc14871d.tar.gz
XMonadContrib-10126d6a3de14c93ee13f646e7ede0a6cc14871d.tar.xz
XMonadContrib-10126d6a3de14c93ee13f646e7ede0a6cc14871d.zip
Named: reimplemented as a LayoutModifier and updated Config.Droundy accordingly
darcs-hash:20080128161343-32816-850ccc526022c8bade35c0cb22581577785fede7.gz
Diffstat (limited to 'XMonad/Layout/Named.hs')
-rw-r--r--XMonad/Layout/Named.hs30
1 files changed, 13 insertions, 17 deletions
diff --git a/XMonad/Layout/Named.hs b/XMonad/Layout/Named.hs
index 48a29c3..a186609 100644
--- a/XMonad/Layout/Named.hs
+++ b/XMonad/Layout/Named.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
+{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
@@ -14,13 +14,13 @@
--
-----------------------------------------------------------------------------
-module XMonad.Layout.Named (
- -- * Usage
- -- $usage
- Named(Named)
- ) where
+module XMonad.Layout.Named
+ ( -- * Usage
+ -- $usage
+ named
+ ) where
-import XMonad
+import XMonad.Layout.LayoutModifier
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -30,21 +30,17 @@ import XMonad
-- Then edit your @layoutHook@ by adding the Named layout modifier
-- to some layout:
--
--- > myLayouts = Named "real big" Full ||| etc..
+-- > myLayouts = named "real big" Full ||| etc..
-- > main = xmonad defaultConfig { layoutHook = myLayouts }
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
-data Named l a = Named String (l a) deriving ( Read, Show )
+named :: String -> l a -> ModifiedLayout Named l a
+named s = ModifiedLayout (Named s)
-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')
- emptyLayout (Named n l) r = do (ws, ml') <- emptyLayout l r
- 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
+data Named a = Named String deriving ( Read, Show )
+instance LayoutModifier Named a where
+ modifyDescription (Named n) _ = n