Tabbed.hs, SetWMName.hs: the modules need bitwise "or"

Tabbed.hs cleaned of trailing whitespace.
This commit is contained in:
"Valery V. Vorotyntsev"
2007-11-15 14:37:58 +00:00
parent 33fa0047c9
commit d4f8502807
2 changed files with 18 additions and 16 deletions

View File

@@ -37,6 +37,7 @@ module XMonad.Hooks.SetWMName (
import Control.Monad (join) import Control.Monad (join)
import Control.Monad.Reader (asks) import Control.Monad.Reader (asks)
import Data.Bits ((.|.))
import Data.Char (ord) import Data.Char (ord)
import Data.List (nub) import Data.List (nub)
import Data.Maybe (fromJust, listToMaybe, maybeToList) import Data.Maybe (fromJust, listToMaybe, maybeToList)

View File

@@ -4,16 +4,16 @@
-- Module : XMonad.Layout.Tabbed -- Module : XMonad.Layout.Tabbed
-- Copyright : (c) 2007 David Roundy, Andrea Rossato -- Copyright : (c) 2007 David Roundy, Andrea Rossato
-- License : BSD-style (see xmonad/LICENSE) -- License : BSD-style (see xmonad/LICENSE)
-- --
-- Maintainer : droundy@darcs.net, andrea.rossato@unibz.it -- Maintainer : droundy@darcs.net, andrea.rossato@unibz.it
-- Stability : unstable -- Stability : unstable
-- Portability : unportable -- Portability : unportable
-- --
-- A tabbed layout for the Xmonad Window Manager -- A tabbed layout for the Xmonad Window Manager
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Layout.Tabbed ( module XMonad.Layout.Tabbed (
-- * Usage: -- * Usage:
-- $usage -- $usage
tabbed tabbed
@@ -26,6 +26,7 @@ import Control.Monad.State ( gets )
import Control.Monad.Reader import Control.Monad.Reader
import Data.Maybe import Data.Maybe
import Data.List import Data.List
import Data.Bits ((.|.))
import Graphics.X11.Xlib import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras import Graphics.X11.Xlib.Extras
@@ -51,7 +52,7 @@ import XMonad.Util.XUtils
-- > -- Extension-provided layouts -- > -- Extension-provided layouts
-- > , Layout $ tabbed shrinkText defaultTConf -- > , Layout $ tabbed shrinkText defaultTConf
-- > ] -- > ]
-- > -- >
-- > , ... ] -- > , ... ]
-- --
-- You can also edit the default configuration options. -- You can also edit the default configuration options.
@@ -70,7 +71,7 @@ import XMonad.Util.XUtils
tabbed :: Shrinker s => s -> TConf -> Tabbed s a tabbed :: Shrinker s => s -> TConf -> Tabbed s a
tabbed s t = Tabbed (I Nothing) s t tabbed s t = Tabbed (I Nothing) s t
data TConf = data TConf =
TConf { activeColor :: String TConf { activeColor :: String
, inactiveColor :: String , inactiveColor :: String
, activeBorderColor :: String , activeBorderColor :: String
@@ -82,7 +83,7 @@ data TConf =
} deriving (Show, Read) } deriving (Show, Read)
defaultTConf :: TConf defaultTConf :: TConf
defaultTConf = defaultTConf =
TConf { activeColor = "#999999" TConf { activeColor = "#999999"
, inactiveColor = "#666666" , inactiveColor = "#666666"
, activeBorderColor = "#FFFFFF" , activeBorderColor = "#FFFFFF"
@@ -93,7 +94,7 @@ defaultTConf =
, tabSize = 20 , tabSize = 20
} }
data TabState = data TabState =
TabState { tabsWindows :: [(Window,Window)] TabState { tabsWindows :: [(Window,Window)]
, scr :: Rectangle , scr :: Rectangle
, fontS :: FontStruct -- FontSet , fontS :: FontStruct -- FontSet
@@ -108,7 +109,7 @@ instance Shrinker s => LayoutClass (Tabbed s) Window where
handleMessage = handleMess handleMessage = handleMess
description _ = "Tabbed" description _ = "Tabbed"
doLay :: Shrinker s => Invisible Maybe TabState -> s -> TConf doLay :: Shrinker s => Invisible Maybe TabState -> s -> TConf
-> Rectangle -> W.Stack Window -> X ([(Window, Rectangle)], Maybe (Tabbed s Window)) -> Rectangle -> W.Stack Window -> X ([(Window, Rectangle)], Maybe (Tabbed s Window))
doLay ist ishr c sc (W.Stack w [] []) = do doLay ist ishr c sc (W.Stack w [] []) = do
whenIJust ist $ \st -> mapM_ deleteWindow (map fst $ tabsWindows st) whenIJust ist $ \st -> mapM_ deleteWindow (map fst $ tabsWindows st)
@@ -139,23 +140,23 @@ handleMess _ _ = return Nothing
handleEvent :: Shrinker s => s -> TConf -> TabState -> Event -> X () handleEvent :: Shrinker s => s -> TConf -> TabState -> Event -> X ()
-- button press -- button press
handleEvent ishr conf (TabState {tabsWindows = tws, scr = screen, fontS = fs }) handleEvent ishr conf (TabState {tabsWindows = tws, scr = screen, fontS = fs })
(ButtonEvent {ev_window = thisw, ev_subwindow = thisbw, ev_event_type = t }) (ButtonEvent {ev_window = thisw, ev_subwindow = thisbw, ev_event_type = t })
| t == buttonPress, tl <- map fst tws, thisw `elem` tl || thisbw `elem` tl = do | t == buttonPress, tl <- map fst tws, thisw `elem` tl || thisbw `elem` tl = do
case lookup thisw tws of case lookup thisw tws of
Just x -> do focus x Just x -> do focus x
updateTab ishr conf fs width (thisw, x) updateTab ishr conf fs width (thisw, x)
Nothing -> return () Nothing -> return ()
where width = rect_width screen `div` fromIntegral (length tws) where width = rect_width screen `div` fromIntegral (length tws)
-- propertyNotify -- propertyNotify
handleEvent ishr conf (TabState {tabsWindows = tws, scr = screen, fontS = fs }) handleEvent ishr conf (TabState {tabsWindows = tws, scr = screen, fontS = fs })
(PropertyEvent {ev_window = thisw }) (PropertyEvent {ev_window = thisw })
| thisw `elem` (map snd tws) = do | thisw `elem` (map snd tws) = do
let tabwin = (fst $ fromJust $ find ((== thisw) . snd) tws, thisw) let tabwin = (fst $ fromJust $ find ((== thisw) . snd) tws, thisw)
updateTab ishr conf fs width tabwin updateTab ishr conf fs width tabwin
where width = rect_width screen `div` fromIntegral (length tws) where width = rect_width screen `div` fromIntegral (length tws)
-- expose -- expose
handleEvent ishr conf (TabState {tabsWindows = tws, scr = screen, fontS = fs }) handleEvent ishr conf (TabState {tabsWindows = tws, scr = screen, fontS = fs })
(ExposeEvent {ev_window = thisw }) (ExposeEvent {ev_window = thisw })
| thisw `elem` (map fst tws) = do | thisw `elem` (map fst tws) = do
updateTab ishr conf fs width (thisw, fromJust $ lookup thisw tws) updateTab ishr conf fs width (thisw, fromJust $ lookup thisw tws)
@@ -184,11 +185,11 @@ updateTab :: Shrinker s => s -> TConf -> FontStruct -> Dimension -> (Window,Wind
updateTab ishr c fs wh (tabw,ow) = do updateTab ishr c fs wh (tabw,ow) = do
nw <- getName ow nw <- getName ow
let ht = fromIntegral $ tabSize c :: Dimension let ht = fromIntegral $ tabSize c :: Dimension
focusColor win ic ac = (maybe ic (\focusw -> if focusw == win focusColor win ic ac = (maybe ic (\focusw -> if focusw == win
then ac else ic) . W.peek) then ac else ic) . W.peek)
`fmap` gets windowset `fmap` gets windowset
(bc',borderc',tc') <- focusColor ow (bc',borderc',tc') <- focusColor ow
(inactiveColor c, inactiveBorderColor c, inactiveTextColor c) (inactiveColor c, inactiveBorderColor c, inactiveTextColor c)
(activeColor c, activeBorderColor c, activeTextColor c) (activeColor c, activeBorderColor c, activeTextColor c)
let s = shrinkIt ishr let s = shrinkIt ishr
name = shrinkWhile s (\n -> textWidth fs n > name = shrinkWhile s (\n -> textWidth fs n >
@@ -196,7 +197,7 @@ updateTab ishr c fs wh (tabw,ow) = do
paintAndWrite tabw fs wh ht 1 bc' borderc' tc' bc' AlignCenter name paintAndWrite tabw fs wh ht 1 bc' borderc' tc' bc' AlignCenter name
shrink :: TConf -> Rectangle -> Rectangle shrink :: TConf -> Rectangle -> Rectangle
shrink c (Rectangle x y w h) = shrink c (Rectangle x y w h) =
Rectangle x (y + fromIntegral (tabSize c)) w (h - fromIntegral (tabSize c)) Rectangle x (y + fromIntegral (tabSize c)) w (h - fromIntegral (tabSize c))
shrinkWhile :: (String -> [String]) -> (String -> Bool) -> String -> String shrinkWhile :: (String -> [String]) -> (String -> Bool) -> String -> String