mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
Fix GHC warning: -Wname-shadowing
Related: https://github.com/xmonad/xmonad-contrib/issues/537
This commit is contained in:
parent
b51ccc87b8
commit
673f727206
@ -130,9 +130,9 @@ renameWorkspaceByName w = do old <- gets (currentTag . windowset)
|
||||
sets q = q { current = setscr $ current q }
|
||||
in sets $ removeWorkspace' w s
|
||||
updateIndexMap old w
|
||||
where updateIndexMap old new = do
|
||||
where updateIndexMap oldIM newIM = do
|
||||
wmap <- XS.gets workspaceIndexMap
|
||||
XS.modify $ \s -> s {workspaceIndexMap = Map.map (\t -> if t == old then new else t) wmap}
|
||||
XS.modify $ \s -> s {workspaceIndexMap = Map.map (\t -> if t == oldIM then newIM else t) wmap}
|
||||
|
||||
toNthWorkspace :: (String -> X ()) -> Int -> X ()
|
||||
toNthWorkspace job wnum = do sort <- getSortByIndex
|
||||
|
@ -940,16 +940,16 @@ sortedScreens :: WindowSet -> [Screen]
|
||||
sortedScreens winset = L.sortBy cmp
|
||||
$ W.screens winset
|
||||
where
|
||||
cmp s1 s2 | x1 < x2 = LT
|
||||
| x1 > x2 = GT
|
||||
| y1 < x2 = LT
|
||||
| y1 > y2 = GT
|
||||
cmp s1 s2 | x < x' = LT
|
||||
| x > x' = GT
|
||||
| y < x' = LT
|
||||
| y > y' = GT
|
||||
| otherwise = EQ
|
||||
where
|
||||
(x1, y1) = centerOf (screenRect . W.screenDetail $ s1)
|
||||
(x2, y2) = centerOf (screenRect . W.screenDetail $ s2)
|
||||
(x , y ) = centerOf (screenRect . W.screenDetail $ s1)
|
||||
(x', y') = centerOf (screenRect . W.screenDetail $ s2)
|
||||
|
||||
|
||||
-- | Calculates the L1-distance between two points.
|
||||
lDist :: (Position, Position) -> (Position, Position) -> Int
|
||||
lDist (x1, y1) (x2, y2) = abs (fi $ x1 - x2) + abs (fi $ y1 - y2)
|
||||
lDist (x, y) (x', y') = abs (fi $ x - x') + abs (fi $ y - y')
|
||||
|
@ -73,8 +73,8 @@ instance ExtensionClass Spawner where
|
||||
|
||||
|
||||
getPPIDOf :: ProcessID -> Maybe ProcessID
|
||||
getPPIDOf pid =
|
||||
case unsafePerformIO . tryJust (guard . isDoesNotExistError) . readFile . printf "/proc/%d/stat" $ toInteger pid of
|
||||
getPPIDOf thisPid =
|
||||
case unsafePerformIO . tryJust (guard . isDoesNotExistError) . readFile . printf "/proc/%d/stat" $ toInteger thisPid of
|
||||
Left _ -> Nothing
|
||||
Right contents -> case lines contents of
|
||||
[] -> Nothing
|
||||
@ -83,11 +83,11 @@ getPPIDOf pid =
|
||||
_ -> Nothing
|
||||
|
||||
getPPIDChain :: ProcessID -> [ProcessID]
|
||||
getPPIDChain pid' = ppid_chain pid' []
|
||||
where ppid_chain pid acc =
|
||||
if pid == 0
|
||||
getPPIDChain thisPid = ppid_chain thisPid []
|
||||
where ppid_chain pid' acc =
|
||||
if pid' == 0
|
||||
then acc
|
||||
else case getPPIDOf pid of
|
||||
else case getPPIDOf pid' of
|
||||
Nothing -> acc
|
||||
Just ppid -> ppid_chain ppid (ppid : acc)
|
||||
|
||||
|
@ -521,10 +521,10 @@ dumpProp a _ | a == wM_NAME = dumpString
|
||||
| a == wM_TRANSIENT_FOR = do
|
||||
root <- fromIntegral <$> inX (asks theRoot)
|
||||
w <- asks window
|
||||
WMHints {wmh_window_group = group} <-
|
||||
WMHints {wmh_window_group = wgroup} <-
|
||||
inX $ asks display >>= io . flip getWMHints w
|
||||
dumpExcept [(0 ,"window group " ++ show group)
|
||||
,(root,"window group " ++ show group)
|
||||
dumpExcept [(0 ,"window group " ++ show wgroup)
|
||||
,(root,"window group " ++ show wgroup)
|
||||
]
|
||||
dumpWindow
|
||||
| a == rESOURCE_MANAGER = dumpString
|
||||
|
@ -82,33 +82,32 @@ columnLayout (BinaryColumn scale min_size) rect stack = zip ws rects
|
||||
heights_noflip =
|
||||
let
|
||||
-- Regular case: check for min size.
|
||||
f n size div False = let
|
||||
n_fl = (fromIntegral n)
|
||||
n_prev_fl = (fromIntegral (n + 1))
|
||||
div_test = min (div) (n_prev_fl)
|
||||
f m size divide False = let
|
||||
m_fl = fromIntegral m
|
||||
m_prev_fl = fromIntegral (m + 1)
|
||||
div_test = min divide m_prev_fl
|
||||
value_test = (toInteger (round ((fromIntegral size) / div_test)))
|
||||
value_max = size - (toInteger (min_size * n))
|
||||
value_max = size - toInteger (min_size * m)
|
||||
(value, divide_next, no_room) =
|
||||
if value_test < value_max then
|
||||
(value_test, div, False)
|
||||
(value_test, divide, False)
|
||||
else
|
||||
(value_max, n_fl, True)
|
||||
(value_max, m_fl, True)
|
||||
size_next = size - value
|
||||
n_next = n - 1
|
||||
m_next = m - 1
|
||||
in value
|
||||
: f n_next size_next divide_next no_room
|
||||
: f m_next size_next divide_next no_room
|
||||
-- Fallback case: when windows have reached min size
|
||||
-- simply create an even grid with the remaining space.
|
||||
f n size div True = let
|
||||
n_fl = (fromIntegral n)
|
||||
value_even = ((fromIntegral size) / div)
|
||||
f m size divide True = let
|
||||
divide_next = fromIntegral m
|
||||
value_even = ((fromIntegral size) / divide)
|
||||
value = (toInteger (round value_even))
|
||||
|
||||
n_next = n - 1
|
||||
m_next = m - 1
|
||||
size_next = size - value
|
||||
divide_next = n_fl
|
||||
in value
|
||||
: f n_next size_next n_fl True
|
||||
: f m_next size_next divide_next True
|
||||
-- Last item: included twice.
|
||||
f 0 size _ _noRoomPrev =
|
||||
[size];
|
||||
|
@ -34,7 +34,7 @@ module XMonad.Layout.BinarySpacePartition (
|
||||
) where
|
||||
|
||||
import XMonad
|
||||
import XMonad.Prelude
|
||||
import XMonad.Prelude hiding (insert)
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Util.Stack hiding (Zipper)
|
||||
import XMonad.Util.Types
|
||||
|
@ -159,9 +159,9 @@ marshallPP s pp = pp { ppRename = ppRename pp . unmarshallW
|
||||
whenCurrentOn :: ScreenId -> PP -> PP
|
||||
whenCurrentOn s pp = pp
|
||||
{ ppSort = do
|
||||
sort <- ppSort pp
|
||||
sortWs <- ppSort pp
|
||||
return $ \xs -> case xs of
|
||||
x:_ | unmarshallS (tag x) == s -> sort xs
|
||||
x:_ | unmarshallS (tag x) == s -> sortWs xs
|
||||
_ -> []
|
||||
, ppOrder = \i@(wss:_) -> case wss of
|
||||
"" -> ["\0"] -- we got passed no workspaces; this is the signal from ppSort that this is a boring case
|
||||
|
@ -244,9 +244,9 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
|
||||
-- \"smart space\" in between (the space is not included if the
|
||||
-- 'modifierDescription' is empty).
|
||||
modifyDescription :: (LayoutClass l a) => m a -> l a -> String
|
||||
modifyDescription m l = modifierDescription m <> description l
|
||||
where "" <> x = x
|
||||
x <> y = x ++ " " ++ y
|
||||
modifyDescription m l = modifierDescription m `add` description l
|
||||
where "" `add` x = x
|
||||
x `add` y = x ++ " " ++ y
|
||||
|
||||
-- | The 'LayoutClass' instance for a 'ModifiedLayout' defines the
|
||||
-- semantics of a 'LayoutModifier' applied to an underlying layout.
|
||||
@ -277,4 +277,3 @@ data ModifiedLayout m l a = ModifiedLayout (m a) (l a) deriving ( Read, Show )
|
||||
-- N.B. I think there is a Haddock bug here; the Haddock output for
|
||||
-- the above does not parenthesize (m a) and (l a), which is obviously
|
||||
-- incorrect.
|
||||
|
||||
|
@ -222,14 +222,14 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
|
||||
else splitVerticallyBy frac' r
|
||||
in
|
||||
do
|
||||
(ws1,ml1) <- runLayout (Workspace wid layout1 s1) r1
|
||||
(ws2,ml2) <- runLayout (Workspace wid layout2 s2) r2
|
||||
let newlayout1 = maybe layout1 id ml1
|
||||
newlayout2 = maybe layout2 id ml2
|
||||
(ws , ml ) <- runLayout (Workspace wid layout1 s1) r1
|
||||
(ws', ml') <- runLayout (Workspace wid layout2 s2) r2
|
||||
let newlayout1 = maybe layout1 id ml
|
||||
newlayout2 = maybe layout2 id ml'
|
||||
(f1, str1) = getFocused newlayout1 s1
|
||||
(f2, str2) = getFocused newlayout2 s2
|
||||
fnew = f1 ++ f2
|
||||
return (ws1++ws2, Just $ TMSCombineTwo fnew slst1 slst2 vsp nmaster delta frac newlayout1 newlayout2)
|
||||
return (ws++ws', Just $ TMSCombineTwo fnew slst1 slst2 vsp nmaster delta frac newlayout1 newlayout2)
|
||||
|
||||
|
||||
handleMessage i@(TMSCombineTwo f w1 w2 vsp nmaster delta frac layout1 layout2) m
|
||||
@ -344,23 +344,23 @@ focusWindow w s =
|
||||
then focusSubMasterU w s
|
||||
else focusSubMasterD w s
|
||||
where
|
||||
focusSubMasterU w i@(Stack foc (l:ls) rs) =
|
||||
if foc == w
|
||||
focusSubMasterU win i@(Stack foc (l:ls) rs) =
|
||||
if foc == win
|
||||
then i
|
||||
else
|
||||
if l == w
|
||||
if l == win
|
||||
then news
|
||||
else focusSubMasterU w news
|
||||
else focusSubMasterU win news
|
||||
where news = Stack l ls (foc:rs)
|
||||
focusSubMasterU _ (Stack foc [] rs) =
|
||||
Stack foc [] rs
|
||||
focusSubMasterD w i@(Stack foc ls (r:rs)) =
|
||||
if foc == w
|
||||
focusSubMasterD win i@(Stack foc ls (r:rs)) =
|
||||
if foc == win
|
||||
then i
|
||||
else
|
||||
if r == w
|
||||
if r == win
|
||||
then news
|
||||
else focusSubMasterD w news
|
||||
else focusSubMasterD win news
|
||||
where news = Stack r (foc:ls) rs
|
||||
focusSubMasterD _ (Stack foc ls []) =
|
||||
Stack foc ls []
|
||||
|
@ -100,13 +100,13 @@ searchUnicode entries p s = map (second BS.unpack) $ filter go entries
|
||||
go (_, d) = all (`p` (BS.unpack d)) w
|
||||
|
||||
mkUnicodePrompt :: String -> [String] -> String -> XPConfig -> X ()
|
||||
mkUnicodePrompt prog args unicodeDataFilename config =
|
||||
mkUnicodePrompt prog args unicodeDataFilename xpCfg =
|
||||
whenX (populateEntries unicodeDataFilename) $ do
|
||||
entries <- fmap getUnicodeData (XS.get :: X UnicodeData)
|
||||
mkXPrompt
|
||||
Unicode
|
||||
(config {sorter = sorter config . map toUpper})
|
||||
(unicodeCompl entries $ searchPredicate config)
|
||||
(xpCfg {sorter = sorter xpCfg . map toUpper})
|
||||
(unicodeCompl entries $ searchPredicate xpCfg)
|
||||
paste
|
||||
where
|
||||
unicodeCompl :: [(Char, BS.ByteString)] -> Predicate -> String -> IO [String]
|
||||
|
@ -85,9 +85,9 @@ newTheme :: ThemeInfo
|
||||
newTheme = TI "" "" "" def
|
||||
|
||||
ppThemeInfo :: ThemeInfo -> String
|
||||
ppThemeInfo t = themeName t <> themeDescription t <> "by" <> themeAuthor t
|
||||
where "" <> x = x
|
||||
x <> y = x ++ " - " ++ y
|
||||
ppThemeInfo t = themeName t `add` themeDescription t `add` "by" `add` themeAuthor t
|
||||
where "" `add` x = x
|
||||
x `add` y = x ++ " - " ++ y
|
||||
|
||||
|
||||
listOfThemes :: [ThemeInfo]
|
||||
@ -400,4 +400,3 @@ kavonFireTheme =
|
||||
, inactiveTextColor = "black"
|
||||
}
|
||||
}
|
||||
|
||||
|
Loading…
x
Reference in New Issue
Block a user