mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-17 13:24:14 -07:00
Various decorations related updates
* remove deprecated TConf stuff * Remove 'style' from DeConf * Change DeConf to Theme * share defaultTheme across all decorations
This commit is contained in:
@@ -17,7 +17,7 @@ module XMonad.Config.Arossato
|
||||
( -- * Usage
|
||||
-- $usage
|
||||
arossatoConfig
|
||||
, arossatoTabbedConfig
|
||||
, arossatoTheme
|
||||
) where
|
||||
|
||||
import qualified Data.Map as M
|
||||
@@ -80,27 +80,16 @@ import XMonad.Util.Run
|
||||
|
||||
-- | My configuration for the Tabbed Layout. Basically this is the
|
||||
-- Ion3 clean style.
|
||||
arossatoTabbedConfig :: DeConfig TabbedDecoration Window
|
||||
arossatoTabbedConfig = defaultTabbedConfig
|
||||
{ activeColor = "#8a999e"
|
||||
, inactiveColor = "#545d75"
|
||||
, activeBorderColor = "white"
|
||||
, inactiveBorderColor = "grey"
|
||||
, activeTextColor = "white"
|
||||
, inactiveTextColor = "grey"
|
||||
, decoHeight = 14
|
||||
}
|
||||
|
||||
arossatoSFConfig :: DeConfig SimpleDecoration Window
|
||||
arossatoSFConfig = defaultSFConfig
|
||||
{ activeColor = "#8a999e"
|
||||
, inactiveColor = "#545d75"
|
||||
, activeBorderColor = "white"
|
||||
, inactiveBorderColor = "grey"
|
||||
, activeTextColor = "white"
|
||||
, inactiveTextColor = "grey"
|
||||
, decoHeight = 14
|
||||
}
|
||||
arossatoTheme :: Theme
|
||||
arossatoTheme = defaultTheme
|
||||
{ activeColor = "#8a999e"
|
||||
, inactiveColor = "#545d75"
|
||||
, activeBorderColor = "white"
|
||||
, inactiveBorderColor = "grey"
|
||||
, activeTextColor = "white"
|
||||
, inactiveTextColor = "grey"
|
||||
, decoHeight = 14
|
||||
}
|
||||
|
||||
arossatoConfig = do
|
||||
xmobar <- spawnPipe "xmobar"
|
||||
@@ -120,8 +109,8 @@ arossatoConfig = do
|
||||
}
|
||||
where
|
||||
-- layouts
|
||||
mytabs = tabDeco shrinkText arossatoTabbedConfig
|
||||
decorated = simpleFloat' shrinkText arossatoSFConfig
|
||||
mytabs = tabbed shrinkText arossatoTheme
|
||||
decorated = simpleFloat' shrinkText arossatoTheme
|
||||
tiled = Tall 1 (3/100) (1/2)
|
||||
otherLays = windowArrange $
|
||||
magnifier tiled |||
|
||||
|
@@ -146,7 +146,7 @@ config = -- withUrgencyHook FocusUrgencyHook $
|
||||
, XMonad.keys = keys
|
||||
}
|
||||
|
||||
mytab = tabbed CustomShrink defaultTConf
|
||||
mytab = tabbed CustomShrink defaultTheme
|
||||
|
||||
instance Shrinker CustomShrink where
|
||||
shrinkIt shr s | Just s' <- dropFromHead " " s = shrinkIt shr s'
|
||||
|
@@ -13,6 +13,7 @@ import XMonad.Hooks.ManageDocks
|
||||
import XMonad.Prompt
|
||||
import XMonad.Prompt.Shell
|
||||
import XMonad.Util.Run (spawnPipe)
|
||||
import XMonad.Layout.DwmStyle
|
||||
|
||||
import qualified Data.Map as M
|
||||
import System.IO (hPutStrLn)
|
||||
@@ -29,7 +30,7 @@ sjanssenConfig = do
|
||||
, ((modm, button2), (\w -> focus w >> windows W.swapMaster))
|
||||
, ((modm.|. shiftMask, button1), (\w -> focus w >> mouseResizeWindow w)) ]
|
||||
, keys = \c -> mykeys c `M.union` keys defaultConfig c
|
||||
, layoutHook = avoidStruts $ smartBorders (tiled Tall ||| tiled Wide ||| Full ||| tabDeco shrinkText myTConf)
|
||||
, layoutHook = dwmStyle shrinkText myTheme $ avoidStruts $ smartBorders (tiled Tall ||| tiled Wide ||| Full ||| tabbed shrinkText myTheme)
|
||||
, manageHook = manageHook defaultConfig <+> manageDocks
|
||||
}
|
||||
where
|
||||
@@ -44,7 +45,7 @@ sjanssenConfig = do
|
||||
]
|
||||
|
||||
myFont = "xft:Bitstream Vera Sans Mono:pixelsize=10"
|
||||
myTConf = defaultTabbedConfig { fontName = myFont }
|
||||
myTheme = defaultTheme { fontName = myFont }
|
||||
myPromptConfig = defaultXPConfig
|
||||
{ position = Top
|
||||
, font = myFont
|
||||
|
@@ -20,7 +20,7 @@ module XMonad.Layout.Decoration
|
||||
decoration
|
||||
, Decoration
|
||||
, DecorationStyle (..)
|
||||
, DeConfig (..), defaultDeConfig, mkDefaultDeConfig
|
||||
, Theme (..), defaultTheme
|
||||
, shrinkText, CustomShrink ( CustomShrink )
|
||||
, Shrinker (..), DefaultShrinker
|
||||
, module XMonad.Layout.LayoutModifier
|
||||
@@ -44,42 +44,40 @@ import XMonad.Util.Font
|
||||
-- For usage examples you can see "XMonad.Layout.SimpleDecoration",
|
||||
-- "XMonad.Layout.Tabbed", "XMonad.Layout.DwmStyle",
|
||||
|
||||
decoration :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a
|
||||
decoration :: (DecorationStyle ds a, Shrinker s) => s -> Theme -> ds a
|
||||
-> l a -> ModifiedLayout (Decoration ds s) l a
|
||||
decoration s c = ModifiedLayout (Decoration (I Nothing) s c)
|
||||
decoration s t ds = ModifiedLayout (Decoration (I Nothing) s t ds)
|
||||
|
||||
data DeConfig ds a =
|
||||
DeConfig { activeColor :: String
|
||||
, inactiveColor :: String
|
||||
, urgentColor :: String
|
||||
, activeBorderColor :: String
|
||||
, inactiveBorderColor :: String
|
||||
, urgentBorderColor :: String
|
||||
, activeTextColor :: String
|
||||
, inactiveTextColor :: String
|
||||
, urgentTextColor :: String
|
||||
, fontName :: String
|
||||
, decoWidth :: Dimension
|
||||
, decoHeight :: Dimension
|
||||
, style :: ds a
|
||||
} deriving (Show, Read)
|
||||
data Theme =
|
||||
Theme { activeColor :: String
|
||||
, inactiveColor :: String
|
||||
, urgentColor :: String
|
||||
, activeBorderColor :: String
|
||||
, inactiveBorderColor :: String
|
||||
, urgentBorderColor :: String
|
||||
, activeTextColor :: String
|
||||
, inactiveTextColor :: String
|
||||
, urgentTextColor :: String
|
||||
, fontName :: String
|
||||
, decoWidth :: Dimension
|
||||
, decoHeight :: Dimension
|
||||
} deriving (Show, Read)
|
||||
|
||||
mkDefaultDeConfig :: DecorationStyle ds a => ds a -> DeConfig ds a
|
||||
mkDefaultDeConfig ds =
|
||||
DeConfig { activeColor = "#999999"
|
||||
, inactiveColor = "#666666"
|
||||
, urgentColor = "#FFFF00"
|
||||
, activeBorderColor = "#FFFFFF"
|
||||
, inactiveBorderColor = "#BBBBBB"
|
||||
, urgentBorderColor = "##00FF00"
|
||||
, activeTextColor = "#FFFFFF"
|
||||
, inactiveTextColor = "#BFBFBF"
|
||||
, urgentTextColor = "#FF0000"
|
||||
, fontName = "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
|
||||
, decoWidth = 200
|
||||
, decoHeight = 20
|
||||
, style = ds
|
||||
}
|
||||
defaultTheme :: Theme
|
||||
defaultTheme =
|
||||
Theme { activeColor = "#999999"
|
||||
, inactiveColor = "#666666"
|
||||
, urgentColor = "#FFFF00"
|
||||
, activeBorderColor = "#FFFFFF"
|
||||
, inactiveBorderColor = "#BBBBBB"
|
||||
, urgentBorderColor = "##00FF00"
|
||||
, activeTextColor = "#FFFFFF"
|
||||
, inactiveTextColor = "#BFBFBF"
|
||||
, urgentTextColor = "#FF0000"
|
||||
, fontName = "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
|
||||
, decoWidth = 200
|
||||
, decoHeight = 20
|
||||
}
|
||||
|
||||
type DecoWin = (Window,Maybe Rectangle)
|
||||
type OrigWin = (Window,Rectangle)
|
||||
@@ -89,7 +87,7 @@ data DecorationState =
|
||||
}
|
||||
|
||||
data Decoration ds s a =
|
||||
Decoration (Invisible Maybe DecorationState) s (DeConfig ds a)
|
||||
Decoration (Invisible Maybe DecorationState) s Theme (ds a)
|
||||
deriving (Show, Read)
|
||||
|
||||
class (Read (ds a), Show (ds a)) => DecorationStyle ds a where
|
||||
@@ -110,18 +108,12 @@ class (Read (ds a), Show (ds a)) => DecorationStyle ds a where
|
||||
-> W.Stack a -> [(a,Rectangle)] -> (a,Rectangle) -> X (Maybe Rectangle)
|
||||
decorate ds w h r s ars ar = return $ pureDecoration ds w h r s ars ar
|
||||
|
||||
data DefaultStyle a = DefaultStyle deriving (Read, Show)
|
||||
instance DecorationStyle DefaultStyle a
|
||||
|
||||
defaultDeConfig :: DeConfig DefaultStyle a
|
||||
defaultDeConfig = mkDefaultDeConfig DefaultStyle
|
||||
|
||||
instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration ds s) Window where
|
||||
redoLayout (Decoration st sh c) sc stack wrs
|
||||
redoLayout (Decoration st sh c ds) sc stack wrs
|
||||
| decorate_first = do whenIJust st $ \s -> do
|
||||
deleteWindows (getDWs $ decos s)
|
||||
releaseXMF (font s)
|
||||
return (wrs, Just $ Decoration (I Nothing) sh c)
|
||||
return (wrs, Just $ Decoration (I Nothing) sh c ds)
|
||||
| I Nothing <- st = initState c wrs >>= processState
|
||||
| I (Just s) <- st = do let dwrs = decos s
|
||||
(d,a) = curry diff (get_ws dwrs) ws
|
||||
@@ -141,40 +133,41 @@ instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration d
|
||||
todel d = filter (flip elem d . get_w)
|
||||
toadd a = filter (flip elem a . fst )
|
||||
|
||||
insert_dwr ((w,r),(dw,Just dr)) xs = (dw,dr):(w, shrink (style c) dr r):xs
|
||||
insert_dwr ((w,r),(dw,Just dr)) xs = (dw,dr):(w, shrink ds dr r):xs
|
||||
insert_dwr (x ,(_ ,Nothing)) xs = x:xs
|
||||
|
||||
resync _ [] = return []
|
||||
resync d ((w,r):xs) = case w `elemIndex` get_ws d of
|
||||
Just i -> do dr <- decorate (style c) (decoWidth c) (decoHeight c) sc stack wrs (w,r)
|
||||
Just i -> do dr <- decorate ds (decoWidth c) (decoHeight c) sc stack wrs (w,r)
|
||||
dwrs <- resync d xs
|
||||
return $ ((w,r),(find_dw i d, dr)) : dwrs
|
||||
Nothing -> resync d xs
|
||||
|
||||
decorate_first = length wrs == 1 && (not . decorateFirst . style $ c)
|
||||
decorate_first = length wrs == 1 && (not . decorateFirst $ ds)
|
||||
processState s = do ndwrs <- resync (decos s) wrs
|
||||
showWindows (getDWs ndwrs)
|
||||
updateDecos sh c (font s) ndwrs
|
||||
return (foldr insert_dwr [] ndwrs, Just (Decoration (I (Just (s {decos = ndwrs}))) sh c))
|
||||
return (foldr insert_dwr [] ndwrs, Just (Decoration (I (Just (s {decos = ndwrs}))) sh c ds))
|
||||
|
||||
handleMess (Decoration (I (Just s@(DS {decos = dwrs}))) sh c) m
|
||||
handleMess (Decoration (I (Just s@(DS {decos = dwrs}))) sh c ds) m
|
||||
| Just e <- fromMessage m :: Maybe Event = handleEvent sh c s e >> return Nothing
|
||||
| Just Hide <- fromMessage m = hideWindows dws >> return Nothing
|
||||
| Just ReleaseResources <- fromMessage m = do deleteWindows dws
|
||||
releaseXMF (font s)
|
||||
return $ Just $ Decoration (I Nothing) sh c
|
||||
return $ Just $ Decoration (I Nothing) sh c ds
|
||||
where dws = getDWs dwrs
|
||||
|
||||
handleMess _ _ = return Nothing
|
||||
|
||||
emptyLayoutMod (Decoration (I (Just (DS dwrs f))) sh c) _ _ = do deleteWindows (getDWs dwrs)
|
||||
releaseXMF f
|
||||
return ([], Just $ Decoration (I Nothing) sh c)
|
||||
emptyLayoutMod (Decoration (I (Just (DS dwrs f))) sh c ds) _ _ = do
|
||||
deleteWindows (getDWs dwrs)
|
||||
releaseXMF f
|
||||
return ([], Just $ Decoration (I Nothing) sh c ds)
|
||||
emptyLayoutMod _ _ _ = return ([], Nothing)
|
||||
|
||||
modifierDescription (Decoration _ _ c) = describeDeco $ style c
|
||||
modifierDescription (Decoration _ _ _ ds) = describeDeco ds
|
||||
|
||||
handleEvent :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a -> DecorationState-> Event -> X ()
|
||||
handleEvent :: Shrinker s => s -> Theme -> DecorationState -> Event -> X ()
|
||||
handleEvent sh c (DS dwrs fs) e
|
||||
| PropertyEvent {ev_window = w} <- e, w `elem` (map (fst . fst) dwrs) = updateDecos sh c fs dwrs
|
||||
| ExposeEvent {ev_window = w} <- e, w `elem` (map (fst . snd) dwrs) = updateDecos sh c fs dwrs
|
||||
@@ -183,13 +176,13 @@ handleEvent _ _ _ _ = return ()
|
||||
getDWs :: [(OrigWin,DecoWin)] -> [Window]
|
||||
getDWs = map (fst . snd)
|
||||
|
||||
initState :: DecorationStyle ds a => DeConfig ds a -> [(Window,Rectangle)] -> X DecorationState
|
||||
initState :: Theme -> [(Window,Rectangle)] -> X DecorationState
|
||||
initState conf wrs = do
|
||||
fs <- initXMF (fontName conf)
|
||||
dwrs <- createDecos conf wrs
|
||||
return $ DS dwrs fs
|
||||
|
||||
createDecos :: DecorationStyle ds a => DeConfig ds a -> [(Window,Rectangle)] -> X [(OrigWin,DecoWin)]
|
||||
createDecos :: Theme -> [(Window,Rectangle)] -> X [(OrigWin,DecoWin)]
|
||||
createDecos _ [] = return []
|
||||
createDecos c (wr:wrs) = do
|
||||
let rect = Rectangle 0 0 1 1
|
||||
@@ -198,10 +191,10 @@ createDecos c (wr:wrs) = do
|
||||
dwrs <- createDecos c wrs
|
||||
return ((wr,(dw,Nothing)):dwrs)
|
||||
|
||||
updateDecos :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a -> XMonadFont -> [(OrigWin, DecoWin)] -> X ()
|
||||
updateDecos :: Shrinker s => s -> Theme -> XMonadFont -> [(OrigWin, DecoWin)] -> X ()
|
||||
updateDecos s c f = mapM_ $ updateDeco s c f
|
||||
|
||||
updateDeco :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a -> XMonadFont -> (OrigWin, DecoWin) -> X ()
|
||||
updateDeco :: Shrinker s => s -> Theme -> XMonadFont -> (OrigWin, DecoWin) -> X ()
|
||||
updateDeco sh c fs ((w,_),(dw,Just (Rectangle _ _ wh ht))) = do
|
||||
nw <- getName w
|
||||
ur <- readUrgents
|
||||
|
@@ -16,8 +16,9 @@ module XMonad.Layout.DwmStyle
|
||||
( -- * Usage:
|
||||
-- $usage
|
||||
dwmStyle
|
||||
, DeConfig (..)
|
||||
, DwmStyle (..), defaultDwmStyleConfig
|
||||
, Theme (..)
|
||||
, defaultTheme
|
||||
, DwmStyle (..)
|
||||
, shrinkText, CustomShrink(CustomShrink)
|
||||
, Shrinker(..)
|
||||
) where
|
||||
@@ -35,7 +36,7 @@ import XMonad.Layout.Decoration
|
||||
-- Then edit your @layoutHook@ by adding the DwmStyle decoration to
|
||||
-- your layout:
|
||||
--
|
||||
-- > myL = dwmStyle shrinkText defaultDwmStyleConfig (layoutHook defaultConfig)
|
||||
-- > myL = dwmStyle shrinkText defaultTheme (layoutHook defaultConfig)
|
||||
-- > main = xmonad defaultConfig { layoutHook = myL }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
@@ -44,7 +45,7 @@ import XMonad.Layout.Decoration
|
||||
--
|
||||
-- You can also edit the default configuration options.
|
||||
--
|
||||
-- > myDWConfig = defaultDwmStyleConfig { inactiveBorderColor = "red"
|
||||
-- > myDWConfig = defaultTheme { inactiveBorderColor = "red"
|
||||
-- > , inactiveTextColor = "red"}
|
||||
--
|
||||
-- and
|
||||
@@ -52,12 +53,9 @@ import XMonad.Layout.Decoration
|
||||
-- > myL = dwmStyle shrinkText myDWConfig (layoutHook defaultConfig)
|
||||
|
||||
-- | Add simple old dwm-style decorations to windows of a layout.
|
||||
dwmStyle :: (Eq a, Shrinker s) => s -> DeConfig DwmStyle a
|
||||
dwmStyle :: (Eq a, Shrinker s) => s -> Theme
|
||||
-> l a -> ModifiedLayout (Decoration DwmStyle s) l a
|
||||
dwmStyle s c = decoration s c
|
||||
|
||||
defaultDwmStyleConfig :: Eq a => DeConfig DwmStyle a
|
||||
defaultDwmStyleConfig= mkDefaultDeConfig Dwm
|
||||
dwmStyle s c = decoration s c Dwm
|
||||
|
||||
data DwmStyle a = Dwm deriving (Show, Read)
|
||||
|
||||
|
@@ -17,8 +17,8 @@ module XMonad.Layout.SimpleDecoration
|
||||
( -- * Usage:
|
||||
-- $usage
|
||||
simpleDeco
|
||||
, DeConfig (..)
|
||||
, SimpleDecoration (..), defaultSimpleConfig
|
||||
, Theme (..)
|
||||
, SimpleDecoration (..)
|
||||
, shrinkText, CustomShrink(CustomShrink)
|
||||
, Shrinker(..)
|
||||
) where
|
||||
@@ -35,7 +35,7 @@ import XMonad.Layout.Decoration
|
||||
-- Then edit your @layoutHook@ by adding the SimpleDecoration decoration to
|
||||
-- your layout:
|
||||
--
|
||||
-- > myL = simpleDeco shrinkText defaultSimpleConfig (layoutHook defaultConfig)
|
||||
-- > myL = simpleDeco shrinkText defaultTheme (layoutHook defaultConfig)
|
||||
-- > main = xmonad defaultConfig { layoutHook = myL }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
@@ -44,20 +44,17 @@ import XMonad.Layout.Decoration
|
||||
--
|
||||
-- You can also edit the default configuration options.
|
||||
--
|
||||
-- > mySDConfig = defaultSimpleConfig { inactiveBorderColor = "red"
|
||||
-- > mySDConfig = defaultTheme { inactiveBorderColor = "red"
|
||||
-- > , inactiveTextColor = "red"}
|
||||
--
|
||||
-- and
|
||||
--
|
||||
-- > myL = dwmStyle shrinkText mySDConfig (layoutHook defaultConfig)
|
||||
-- > myL = dwmStyle shrinkText mySDConfig (layoutHook defaultTheme)
|
||||
|
||||
-- | Add simple decorations to windows of a layout.
|
||||
simpleDeco :: Shrinker s => s -> DeConfig SimpleDecoration a
|
||||
simpleDeco :: Shrinker s => s -> Theme
|
||||
-> l a -> ModifiedLayout (Decoration SimpleDecoration s) l a
|
||||
simpleDeco s c = decoration s c
|
||||
|
||||
defaultSimpleConfig :: DeConfig SimpleDecoration a
|
||||
defaultSimpleConfig = mkDefaultDeConfig $ Simple True
|
||||
simpleDeco s c = decoration s c $ Simple True
|
||||
|
||||
data SimpleDecoration a = Simple Bool deriving (Show, Read)
|
||||
|
||||
@@ -67,4 +64,4 @@ instance DecorationStyle SimpleDecoration a where
|
||||
if b then Rectangle x (y + fi dh) w (h - dh) else r
|
||||
pureDecoration (Simple b) wh ht _ _ _ (_,Rectangle x y wid _) =
|
||||
if b then Just $ Rectangle x y nwh ht else Just $ Rectangle x (y - fi ht) nwh ht
|
||||
where nwh = min wid wh
|
||||
where nwh = min wid wh
|
||||
|
@@ -17,7 +17,7 @@ module XMonad.Layout.SimpleFloat
|
||||
-- $usage
|
||||
simpleFloat
|
||||
, simpleFloat'
|
||||
, SimpleDecoration (..), defaultSFConfig
|
||||
, SimpleDecoration (..)
|
||||
, shrinkText, CustomShrink(CustomShrink)
|
||||
, Shrinker(..)
|
||||
) where
|
||||
@@ -46,16 +46,13 @@ import XMonad.Layout.WindowArranger
|
||||
-- | FIXME
|
||||
simpleFloat :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
|
||||
(ModifiedLayout WindowArranger SimpleFloat) a
|
||||
simpleFloat = decoration shrinkText defaultSFConfig (windowArrangeAll $ SF 20)
|
||||
simpleFloat = decoration shrinkText defaultTheme (Simple False) (windowArrangeAll $ SF 20)
|
||||
|
||||
-- | FIXME
|
||||
simpleFloat' :: Shrinker s => s -> DeConfig SimpleDecoration a ->
|
||||
simpleFloat' :: Shrinker s => s -> Theme ->
|
||||
ModifiedLayout (Decoration SimpleDecoration s)
|
||||
(ModifiedLayout WindowArranger SimpleFloat) a
|
||||
simpleFloat' s c = decoration s c (windowArrangeAll $ SF (decoHeight c))
|
||||
|
||||
defaultSFConfig :: DeConfig SimpleDecoration a
|
||||
defaultSFConfig = mkDefaultDeConfig $ Simple False
|
||||
simpleFloat' s c = decoration s c (Simple False) (windowArrangeAll $ SF (decoHeight c))
|
||||
|
||||
data SimpleFloat a = SF Dimension deriving (Show, Read)
|
||||
instance LayoutClass SimpleFloat Window where
|
||||
|
@@ -12,22 +12,15 @@
|
||||
--
|
||||
-- A tabbed layout for the Xmonad Window Manager
|
||||
--
|
||||
-- This module has functions and types that conflict with those used
|
||||
-- in Decoration.hs. These functions and types are deprecated and will
|
||||
-- be removed.
|
||||
--
|
||||
-- PLEASE: do not use 'tabbed'. Use 'tabDeco' instead.
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module XMonad.Layout.Tabbed
|
||||
( -- * Usage:
|
||||
-- $usage
|
||||
tabbed
|
||||
, tabDeco
|
||||
, defaultTConf
|
||||
, DeConfig (..)
|
||||
, TabbedDecoration (..), defaultTabbedConfig
|
||||
, Theme (..)
|
||||
, defaultTheme
|
||||
, TabbedDecoration (..)
|
||||
, shrinkText, CustomShrink(CustomShrink)
|
||||
, Shrinker(..)
|
||||
) where
|
||||
@@ -38,7 +31,6 @@ import Data.List
|
||||
import XMonad
|
||||
import qualified XMonad.StackSet as S
|
||||
import XMonad.Layout.Decoration
|
||||
import XMonad.Layout.Simplest
|
||||
|
||||
-- $usage
|
||||
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
|
||||
@@ -47,7 +39,7 @@ import XMonad.Layout.Simplest
|
||||
--
|
||||
-- Then edit your @layoutHook@ by adding the Tabbed layout:
|
||||
--
|
||||
-- > myLayouts = tabDeco shrinkText defaultTabbedConfig ||| Full ||| etc..
|
||||
-- > myLayouts = tabDeco shrinkText defaultTheme ||| Full ||| etc..
|
||||
-- > main = xmonad defaultConfig { layoutHook = myLayouts }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
@@ -56,25 +48,17 @@ import XMonad.Layout.Simplest
|
||||
--
|
||||
-- You can also edit the default configuration options.
|
||||
--
|
||||
-- > myTabConfig = defaultTabbedConfig { inactiveBorderColor = "#FF0000"
|
||||
-- > myTabConfig = defaultTheme { inactiveBorderColor = "#FF0000"
|
||||
-- > , activeTextColor = "#00FF00"}
|
||||
--
|
||||
-- and
|
||||
--
|
||||
-- > mylayout = tabDeco shrinkText myTabConfig ||| Full ||| etc..
|
||||
|
||||
-- | Create a tabbed layout with a shrinker and a tabbed configuration.
|
||||
tabDeco :: (Eq a, Shrinker s) => s -> DeConfig TabbedDecoration a
|
||||
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
|
||||
tabDeco s c = decoration s c Simplest
|
||||
|
||||
-- | This function is deprecated and will be removed before 0.7!!
|
||||
tabbed :: (Eq a, Shrinker s) => s -> TConf
|
||||
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
|
||||
tabbed s c = decoration s (toNewConf c) Simplest
|
||||
|
||||
defaultTabbedConfig :: Eq a => DeConfig TabbedDecoration a
|
||||
defaultTabbedConfig = mkDefaultDeConfig $ Tabbed
|
||||
tabbed :: (Eq a, Shrinker s) => s -> Theme
|
||||
-> ModifiedLayout (Decoration TabbedDecoration s) Full a
|
||||
tabbed s c = decoration s c Tabbed Full
|
||||
|
||||
data TabbedDecoration a = Tabbed deriving (Read, Show)
|
||||
|
||||
@@ -86,53 +70,3 @@ instance Eq a => DecorationStyle TabbedDecoration a where
|
||||
nx = case w `elemIndex` (S.integrate s) of
|
||||
Just i -> x + (fi nwh * fi i)
|
||||
Nothing -> x
|
||||
|
||||
-- Backward compatibility stuff
|
||||
-- DEPRECATED!!
|
||||
toNewConf :: Eq a => TConf -> DeConfig TabbedDecoration a
|
||||
toNewConf oc =
|
||||
nc { XMonad.Layout.Decoration.activeColor = XMonad.Layout.Tabbed.activeColor oc
|
||||
, XMonad.Layout.Decoration.inactiveColor = XMonad.Layout.Tabbed.inactiveColor oc
|
||||
, XMonad.Layout.Decoration.urgentColor = XMonad.Layout.Tabbed.urgentColor oc
|
||||
, XMonad.Layout.Decoration.activeBorderColor = XMonad.Layout.Tabbed.activeBorderColor oc
|
||||
, XMonad.Layout.Decoration.inactiveBorderColor = XMonad.Layout.Tabbed.inactiveBorderColor oc
|
||||
, XMonad.Layout.Decoration.urgentBorderColor = XMonad.Layout.Tabbed.urgentBorderColor oc
|
||||
, XMonad.Layout.Decoration.activeTextColor = XMonad.Layout.Tabbed.activeTextColor oc
|
||||
, XMonad.Layout.Decoration.inactiveTextColor = XMonad.Layout.Tabbed.inactiveTextColor oc
|
||||
, XMonad.Layout.Decoration.urgentTextColor = XMonad.Layout.Tabbed.urgentTextColor oc
|
||||
, XMonad.Layout.Decoration.fontName = XMonad.Layout.Tabbed.fontName oc
|
||||
, XMonad.Layout.Decoration.decoHeight = fi $ XMonad.Layout.Tabbed.tabSize oc
|
||||
}
|
||||
where nc = mkDefaultDeConfig $ Tabbed
|
||||
|
||||
-- | This datatype is deprecated and will be removed before 0.7!!
|
||||
data TConf =
|
||||
TConf { activeColor :: String
|
||||
, inactiveColor :: String
|
||||
, urgentColor :: String
|
||||
, activeBorderColor :: String
|
||||
, inactiveBorderColor :: String
|
||||
, urgentBorderColor :: String
|
||||
, activeTextColor :: String
|
||||
, inactiveTextColor :: String
|
||||
, urgentTextColor :: String
|
||||
, fontName :: String
|
||||
, tabSize :: Int
|
||||
} deriving (Show, Read)
|
||||
|
||||
-- | This function is deprecated and will be removed before 0.7!!
|
||||
defaultTConf :: TConf
|
||||
defaultTConf =
|
||||
TConf { XMonad.Layout.Tabbed.activeColor = "#999999"
|
||||
, XMonad.Layout.Tabbed.inactiveColor = "#666666"
|
||||
, XMonad.Layout.Tabbed.urgentColor = "#FFFF00"
|
||||
, XMonad.Layout.Tabbed.activeBorderColor = "#FFFFFF"
|
||||
, XMonad.Layout.Tabbed.inactiveBorderColor = "#BBBBBB"
|
||||
, XMonad.Layout.Tabbed.urgentBorderColor = "##00FF00"
|
||||
, XMonad.Layout.Tabbed.activeTextColor = "#FFFFFF"
|
||||
, XMonad.Layout.Tabbed.inactiveTextColor = "#BFBFBF"
|
||||
, XMonad.Layout.Tabbed.urgentTextColor = "#FF0000"
|
||||
, XMonad.Layout.Tabbed.fontName = "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
|
||||
, XMonad.Layout.Tabbed.tabSize = 20
|
||||
}
|
||||
|
||||
|
Reference in New Issue
Block a user