mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 20:21:51 -07:00
Fix partial uses of head
Fixes: https://github.com/xmonad/xmonad-contrib/issues/830 Related: https://github.com/xmonad/xmonad-contrib/pull/836
This commit is contained in:
@@ -28,7 +28,7 @@ module XMonad.Layout.Combo (
|
||||
|
||||
import XMonad hiding (focus)
|
||||
import XMonad.Layout.WindowNavigation (MoveWindowToWindow (..))
|
||||
import XMonad.Prelude (delete, fromMaybe, intersect, isJust, (\\))
|
||||
import XMonad.Prelude (delete, fromMaybe, intersect, isJust, (\\), listToMaybe)
|
||||
import XMonad.StackSet (Stack (..), Workspace (..), integrate')
|
||||
import XMonad.Util.Stack (zipperFocusedAtFirstOf)
|
||||
|
||||
@@ -124,9 +124,9 @@ instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a,
|
||||
msuper' <- broadcastPrivate m [super]
|
||||
if isJust msuper' || isJust ml1' || isJust ml2'
|
||||
then return $ Just $ C2 f ws2
|
||||
(maybe super head msuper')
|
||||
(maybe l1 head ml1')
|
||||
(maybe l2 head ml2')
|
||||
(fromMaybe super (listToMaybe =<< msuper'))
|
||||
(fromMaybe l1 (listToMaybe =<< ml1'))
|
||||
(fromMaybe l2 (listToMaybe =<< ml2'))
|
||||
else return Nothing
|
||||
description (C2 _ _ super l1 l2) = "combining "++ description l1 ++" and "++
|
||||
description l2 ++" with "++ description super
|
||||
|
@@ -97,7 +97,7 @@ instance LayoutClass MultiCol a where
|
||||
where resize Shrink = l { multiColSize = max (-0.5) $ s-ds }
|
||||
resize Expand = l { multiColSize = min 1 $ s+ds }
|
||||
incmastern (IncMasterN x) = l { multiColNWin = take a n ++ [newval] ++ drop 1 r }
|
||||
where newval = max 0 $ head r + x
|
||||
where newval = max 0 $ maybe 0 (x +) (listToMaybe r)
|
||||
r = drop a n
|
||||
n = multiColNWin l
|
||||
ds = multiColDeltaSize l
|
||||
|
@@ -55,23 +55,25 @@ oneBigMessage (OneBig cx cy) m = fmap resize (fromMessage m)
|
||||
|
||||
-- | Main layout function
|
||||
oneBigLayout :: OneBig a -> Rectangle -> W.Stack a -> [(a, Rectangle)]
|
||||
oneBigLayout (OneBig cx cy) rect stack = [(master,masterRect)]
|
||||
++ divideBottom bottomRect bottomWs
|
||||
++ divideRight rightRect rightWs
|
||||
where ws = W.integrate stack
|
||||
n = length ws
|
||||
ht (Rectangle _ _ _ hh) = hh
|
||||
wd (Rectangle _ _ ww _) = ww
|
||||
h' = round (fromIntegral (ht rect)*cy)
|
||||
w = wd rect
|
||||
m = calcBottomWs n w h'
|
||||
master = head ws
|
||||
other = drop 1 ws
|
||||
bottomWs = take m other
|
||||
rightWs = drop m other
|
||||
masterRect = cmaster n m cx cy rect
|
||||
bottomRect = cbottom cy rect
|
||||
rightRect = cright cx cy rect
|
||||
oneBigLayout (OneBig cx cy) rect stack =
|
||||
let ws = W.integrate stack
|
||||
n = length ws
|
||||
in case ws of
|
||||
[] -> []
|
||||
(master : other) -> [(master,masterRect)]
|
||||
++ divideBottom bottomRect bottomWs
|
||||
++ divideRight rightRect rightWs
|
||||
where
|
||||
ht (Rectangle _ _ _ hh) = hh
|
||||
wd (Rectangle _ _ ww _) = ww
|
||||
h' = round (fromIntegral (ht rect)*cy)
|
||||
w = wd rect
|
||||
m = calcBottomWs n w h'
|
||||
bottomWs = take m other
|
||||
rightWs = drop m other
|
||||
masterRect = cmaster n m cx cy rect
|
||||
bottomRect = cbottom cy rect
|
||||
rightRect = cright cx cy rect
|
||||
|
||||
-- | Calculate how many windows must be placed at bottom
|
||||
calcBottomWs :: Int -> Dimension -> Dimension -> Int
|
||||
|
@@ -1,5 +1,9 @@
|
||||
-- {-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, TypeSynonymInstances, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE PatternGuards, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
|
||||
---------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Layout.TallMastersCombo
|
||||
@@ -45,7 +49,7 @@ import XMonad hiding (focus, (|||))
|
||||
import qualified XMonad.Layout as LL
|
||||
import XMonad.Layout.Decoration
|
||||
import XMonad.Layout.Simplest (Simplest (..))
|
||||
import XMonad.Prelude (delete, find, foldM, fromMaybe, isJust)
|
||||
import XMonad.Prelude (delete, find, foldM, fromMaybe, isJust, listToMaybe)
|
||||
import XMonad.StackSet (Stack (..), Workspace (..), integrate')
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Util.Stack (zipperFocusedAtFirstOf)
|
||||
@@ -245,14 +249,14 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
|
||||
return $ mergeSubLayouts mlayout1 mlayout2 (TMSCombineTwo f w1 w2 (not vsp) nmaster delta frac layout1 layout2) True
|
||||
| Just SwapSubMaster <- fromMessage m =
|
||||
-- first get the submaster window
|
||||
let subMaster = if null w2 then Nothing else Just $ head w2
|
||||
let subMaster = listToMaybe w2
|
||||
in case subMaster of
|
||||
Just mw -> do windows $ W.modify' $ swapWindow mw
|
||||
return Nothing
|
||||
Nothing -> return Nothing
|
||||
| Just FocusSubMaster <- fromMessage m =
|
||||
-- first get the submaster window
|
||||
let subMaster = if null w2 then Nothing else Just $ head w2
|
||||
let subMaster = listToMaybe w2
|
||||
in case subMaster of
|
||||
Just mw -> do windows $ W.modify' $ focusWindow mw
|
||||
return Nothing
|
||||
|
Reference in New Issue
Block a user