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