Named: reimplemented as a LayoutModifier and updated Config.Droundy accordingly

This commit is contained in:
Andrea Rossato
2008-01-28 16:13:43 +00:00
parent 6912227914
commit f23a87f4e6
2 changed files with 17 additions and 21 deletions

View File

@@ -133,10 +133,10 @@ config = -- withUrgencyHook FocusUrgencyHook $
, XMonad.workspaces = ["1:mutt","2:iceweasel"] , XMonad.workspaces = ["1:mutt","2:iceweasel"]
, layoutHook = workspaceDir "~" $ windowNavigation $ , layoutHook = workspaceDir "~" $ windowNavigation $
toggleLayouts (noBorders Full) $ avoidStruts $ toggleLayouts (noBorders Full) $ avoidStruts $
Named "tabbed" (noBorders mytab) ||| named "tabbed" (noBorders mytab) |||
Named "xclock" (mytab ****//* combineTwo Square mytab mytab) ||| named "xclock" (mytab ****//* combineTwo Square mytab mytab) |||
Named "three" (mytab **//* mytab *//* combineTwo Square mytab mytab) ||| named "three" (mytab **//* mytab *//* combineTwo Square mytab mytab) |||
Named "widescreen" ((mytab *||* mytab) named "widescreen" ((mytab *||* mytab)
****//* combineTwo Square mytab mytab) -- ||| ****//* combineTwo Square mytab mytab) -- |||
--mosaic 0.25 0.5 --mosaic 0.25 0.5
, terminal = "xterm" -- The preferred terminal program. , terminal = "xterm" -- The preferred terminal program.

View File

@@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-} {-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@@ -14,13 +14,13 @@
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Layout.Named ( module XMonad.Layout.Named
-- * Usage ( -- * Usage
-- $usage -- $usage
Named(Named) named
) where ) where
import XMonad import XMonad.Layout.LayoutModifier
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- 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 -- Then edit your @layoutHook@ by adding the Named layout modifier
-- to some layout: -- to some layout:
-- --
-- > myLayouts = Named "real big" Full ||| etc.. -- > myLayouts = named "real big" Full ||| etc..
-- > main = xmonad defaultConfig { layoutHook = myLayouts } -- > main = xmonad defaultConfig { layoutHook = myLayouts }
-- --
-- For more detailed instructions on editing the layoutHook see: -- For more detailed instructions on editing the layoutHook see:
-- --
-- "XMonad.Doc.Extending#Editing_the_layout_hook" -- "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 data Named a = Named String deriving ( Read, Show )
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
instance LayoutModifier Named a where
modifyDescription (Named n) _ = n