mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-01 20:51:52 -07:00
Fix GHC warning: -Wunused-matches
Related: https://github.com/xmonad/xmonad-contrib/issues/537
This commit is contained in:
@@ -110,7 +110,7 @@ columnLayout (BinaryColumn scale min_size) rect stack = zip ws rects
|
|||||||
in value
|
in value
|
||||||
: f n_next size_next n_fl True
|
: f n_next size_next n_fl True
|
||||||
-- Last item: included twice.
|
-- Last item: included twice.
|
||||||
f 0 size div no_room_prev =
|
f 0 size _ _noRoomPrev =
|
||||||
[size];
|
[size];
|
||||||
in f
|
in f
|
||||||
n_init size_init divide_init False
|
n_init size_init divide_init False
|
||||||
|
@@ -309,12 +309,12 @@ findTheClosestRightmostLeaf s@(_, (LeftCrumb _ _):_) = goUp s >>= goRight >>= fi
|
|||||||
splitShiftLeftCurrent :: Zipper Split -> Maybe (Zipper Split)
|
splitShiftLeftCurrent :: Zipper Split -> Maybe (Zipper Split)
|
||||||
splitShiftLeftCurrent l@(_, []) = Just l
|
splitShiftLeftCurrent l@(_, []) = Just l
|
||||||
splitShiftLeftCurrent l@(_, (RightCrumb _ _):_) = Just l -- Do nothing. We can swap windows instead.
|
splitShiftLeftCurrent l@(_, (RightCrumb _ _):_) = Just l -- Do nothing. We can swap windows instead.
|
||||||
splitShiftLeftCurrent l@(n, c:cs) = removeCurrent l >>= findTheClosestLeftmostLeaf >>= insertRightLeaf n
|
splitShiftLeftCurrent l@(n, _) = removeCurrent l >>= findTheClosestLeftmostLeaf >>= insertRightLeaf n
|
||||||
|
|
||||||
splitShiftRightCurrent :: Zipper Split -> Maybe (Zipper Split)
|
splitShiftRightCurrent :: Zipper Split -> Maybe (Zipper Split)
|
||||||
splitShiftRightCurrent l@(_, []) = Just l
|
splitShiftRightCurrent l@(_, []) = Just l
|
||||||
splitShiftRightCurrent l@(_, (LeftCrumb _ _):_) = Just l -- Do nothing. We can swap windows instead.
|
splitShiftRightCurrent l@(_, (LeftCrumb _ _):_) = Just l -- Do nothing. We can swap windows instead.
|
||||||
splitShiftRightCurrent l@(n, c:cs) = removeCurrent l >>= findTheClosestRightmostLeaf >>= insertLeftLeaf n
|
splitShiftRightCurrent l@(n, _) = removeCurrent l >>= findTheClosestRightmostLeaf >>= insertLeftLeaf n
|
||||||
|
|
||||||
isAllTheWay :: Direction2D -> Zipper Split -> Bool
|
isAllTheWay :: Direction2D -> Zipper Split -> Bool
|
||||||
isAllTheWay _ (_, []) = True
|
isAllTheWay _ (_, []) = True
|
||||||
|
@@ -153,7 +153,7 @@ instance LayoutClass RowsOrColumns a where
|
|||||||
then splitVertically len r
|
then splitVertically len r
|
||||||
else splitHorizontally len r
|
else splitHorizontally len r
|
||||||
|
|
||||||
pureMessage (RowsOrColumns rows) m
|
pureMessage RowsOrColumns{} m
|
||||||
| Just Row <- fromMessage m = Just $ RowsOrColumns True
|
| Just Row <- fromMessage m = Just $ RowsOrColumns True
|
||||||
| Just Col <- fromMessage m = Just $ RowsOrColumns False
|
| Just Col <- fromMessage m = Just $ RowsOrColumns False
|
||||||
| otherwise = Nothing
|
| otherwise = Nothing
|
||||||
@@ -215,7 +215,7 @@ instance Message ChangeFocus
|
|||||||
instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombineTwo l1 l2) Window where
|
instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombineTwo l1 l2) Window where
|
||||||
description _ = "TallMasters"
|
description _ = "TallMasters"
|
||||||
|
|
||||||
runLayout (Workspace wid l@(TMSCombineTwo f w1 w2 vsp nmaster delta frac layout1 layout2) s) r =
|
runLayout (Workspace wid (TMSCombineTwo f _ _ vsp nmaster delta frac layout1 layout2) s) r =
|
||||||
let (s1,s2,frac',slst1,slst2) = splitStack f nmaster frac s
|
let (s1,s2,frac',slst1,slst2) = splitStack f nmaster frac s
|
||||||
(r1, r2) = if vsp
|
(r1, r2) = if vsp
|
||||||
then splitHorizontallyBy frac' r
|
then splitHorizontallyBy frac' r
|
||||||
@@ -352,7 +352,7 @@ focusWindow w s =
|
|||||||
then news
|
then news
|
||||||
else focusSubMasterU w news
|
else focusSubMasterU w news
|
||||||
where news = Stack l ls (foc:rs)
|
where news = Stack l ls (foc:rs)
|
||||||
focusSubMasterU w (Stack foc [] rs) =
|
focusSubMasterU _ (Stack foc [] rs) =
|
||||||
Stack foc [] rs
|
Stack foc [] rs
|
||||||
focusSubMasterD w i@(Stack foc ls (r:rs)) =
|
focusSubMasterD w i@(Stack foc ls (r:rs)) =
|
||||||
if foc == w
|
if foc == w
|
||||||
@@ -362,7 +362,7 @@ focusWindow w s =
|
|||||||
then news
|
then news
|
||||||
else focusSubMasterD w news
|
else focusSubMasterD w news
|
||||||
where news = Stack r (foc:ls) rs
|
where news = Stack r (foc:ls) rs
|
||||||
focusSubMasterD w (Stack foc ls []) =
|
focusSubMasterD _ (Stack foc ls []) =
|
||||||
Stack foc ls []
|
Stack foc ls []
|
||||||
|
|
||||||
-- | Merge two Maybe sublayouts.
|
-- | Merge two Maybe sublayouts.
|
||||||
@@ -441,7 +441,7 @@ handle :: (LayoutClass l a, Message m) => l a -> m -> X (Maybe (l a))
|
|||||||
handle l m = handleMessage l (SomeMessage m)
|
handle l m = handleMessage l (SomeMessage m)
|
||||||
|
|
||||||
instance (GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a where
|
instance (GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a where
|
||||||
description (ChooseWrapper d l r lr) = description lr
|
description (ChooseWrapper _ _ _ lr) = description lr
|
||||||
|
|
||||||
runLayout (Workspace wid (ChooseWrapper d l r lr) s) rec =
|
runLayout (Workspace wid (ChooseWrapper d l r lr) s) rec =
|
||||||
do
|
do
|
||||||
@@ -458,7 +458,7 @@ instance (GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a w
|
|||||||
mlrf <- handle c NextNoWrap
|
mlrf <- handle c NextNoWrap
|
||||||
fstf <- handle c FirstLayout
|
fstf <- handle c FirstLayout
|
||||||
let mlf = elseOr fstf mlrf
|
let mlf = elseOr fstf mlrf
|
||||||
(d',l',r') = case mlf of Just (ChooseWrapper d0 l0 r0 lr0) -> (d0,l0,r0)
|
(d',l',r') = case mlf of Just (ChooseWrapper d0 l0 r0 _) -> (d0,l0,r0)
|
||||||
Nothing -> (d,l,r)
|
Nothing -> (d,l,r)
|
||||||
case mlr' of Just lrt -> return $ Just $ ChooseWrapper d' l' r' lrt
|
case mlr' of Just lrt -> return $ Just $ ChooseWrapper d' l' r' lrt
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
@@ -505,7 +505,7 @@ instance (GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a w
|
|||||||
-- a subclass of layout, which contain extra method to return focused window in sub-layouts
|
-- a subclass of layout, which contain extra method to return focused window in sub-layouts
|
||||||
class (LayoutClass l a) => GetFocused l a where
|
class (LayoutClass l a) => GetFocused l a where
|
||||||
getFocused :: l a -> Maybe (Stack a) -> ([a], String)
|
getFocused :: l a -> Maybe (Stack a) -> ([a], String)
|
||||||
getFocused l ms =
|
getFocused _ ms =
|
||||||
case ms of (Just s) -> ([focus s], "Base")
|
case ms of (Just s) -> ([focus s], "Base")
|
||||||
Nothing -> ([], "Base")
|
Nothing -> ([], "Base")
|
||||||
savFocused :: l a -> Maybe (Stack a) -> l a
|
savFocused :: l a -> Maybe (Stack a) -> l a
|
||||||
|
@@ -788,7 +788,7 @@ handleCompletion cs = do
|
|||||||
| otherwise = replaceCompletion prevCompl
|
| otherwise = replaceCompletion prevCompl
|
||||||
where
|
where
|
||||||
hlCompl :: String = fromMaybe (command st) $ highlightedItem st l
|
hlCompl :: String = fromMaybe (command st) $ highlightedItem st l
|
||||||
complIndex' :: (Int, Int) = nextComplIndex st (length l)
|
complIndex' :: (Int, Int) = nextComplIndex st
|
||||||
nextHlCompl :: Maybe String = highlightedItem st{ complIndex = complIndex' } cs
|
nextHlCompl :: Maybe String = highlightedItem st{ complIndex = complIndex' } cs
|
||||||
|
|
||||||
isSuffixOfCmd :: Bool = hlCompl `isSuffixOf` command st
|
isSuffixOfCmd :: Bool = hlCompl `isSuffixOf` command st
|
||||||
@@ -905,8 +905,8 @@ bufferOne xs x = (null xs && null x,True)
|
|||||||
|
|
||||||
--Receives an state of the prompt, the size of the autocompletion list and returns the column,row
|
--Receives an state of the prompt, the size of the autocompletion list and returns the column,row
|
||||||
--which should be highlighted next
|
--which should be highlighted next
|
||||||
nextComplIndex :: XPState -> Int -> (Int,Int)
|
nextComplIndex :: XPState -> (Int,Int)
|
||||||
nextComplIndex st nitems = case complWinDim st of
|
nextComplIndex st = case complWinDim st of
|
||||||
Nothing -> (0,0) --no window dims (just destroyed or not created)
|
Nothing -> (0,0) --no window dims (just destroyed or not created)
|
||||||
Just (_,_,_,_,xx,yy) -> let
|
Just (_,_,_,_,xx,yy) -> let
|
||||||
(ncols,nrows) = (length xx, length yy)
|
(ncols,nrows) = (length xx, length yy)
|
||||||
|
@@ -97,7 +97,7 @@ type Predicate = String -> String -> Bool
|
|||||||
searchUnicode :: [(Char, BS.ByteString)] -> Predicate -> String -> [(Char, String)]
|
searchUnicode :: [(Char, BS.ByteString)] -> Predicate -> String -> [(Char, String)]
|
||||||
searchUnicode entries p s = map (second BS.unpack) $ filter go entries
|
searchUnicode entries p s = map (second BS.unpack) $ filter go entries
|
||||||
where w = filter (all isAscii) . filter ((> 1) . length) . words $ map toUpper s
|
where w = filter (all isAscii) . filter ((> 1) . length) . words $ map toUpper s
|
||||||
go (c,d) = all (`p` (BS.unpack d)) w
|
go (_, d) = all (`p` (BS.unpack d)) w
|
||||||
|
|
||||||
mkUnicodePrompt :: String -> [String] -> String -> XPConfig -> X ()
|
mkUnicodePrompt :: String -> [String] -> String -> XPConfig -> X ()
|
||||||
mkUnicodePrompt prog args unicodeDataFilename config =
|
mkUnicodePrompt prog args unicodeDataFilename config =
|
||||||
|
Reference in New Issue
Block a user