From 28fff7c1a25be83d6dce44790c703f98788e3459 Mon Sep 17 00:00:00 2001 From: slotThe Date: Fri, 16 Jul 2021 13:52:20 +0200 Subject: [PATCH 1/4] X.L.NoBorders: Add OnlyFloat This adds a new constructor to Ambiguity to unconditionally remove borders for all floating windows. --- XMonad/Layout/NoBorders.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/XMonad/Layout/NoBorders.hs b/XMonad/Layout/NoBorders.hs index f096c0fc36..1850f139d3 100644 --- a/XMonad/Layout/NoBorders.hs +++ b/XMonad/Layout/NoBorders.hs @@ -279,6 +279,8 @@ instance SetsAmbiguous Ambiguity where in lr == wr1 && (not . or) vu OnlyLayoutFloat -> lr == wr1 + OnlyFloat -> + True _ -> wr1 `R.supersetOf` sr return w1 @@ -288,6 +290,7 @@ instance SetsAmbiguous Ambiguity where | Screen <- amb = [w] | OnlyScreenFloat <- amb = [] | OnlyLayoutFloat <- amb = [] + | OnlyFloat <- amb = [] | OnlyLayoutFloatBelow <- amb = [] | OtherIndicated <- amb , let nonF = map integrate $ W.current wset : W.visible wset @@ -326,6 +329,9 @@ data Ambiguity -- ^ Focus in an empty screen does not count as ambiguous. | OtherIndicated -- ^ No borders on full when all other screens have borders. + | OnlyFloat + -- ^ Remove borders on all floating windows; tiling windows of + -- any kinds are not affected. | Screen -- ^ Borders are never drawn on singleton screens. With this one you -- really need another way such as a statusbar to detect focus. From 220656aab07075736d9017f0e2123691f4e3b974 Mon Sep 17 00:00:00 2001 From: slotThe Date: Fri, 16 Jul 2021 21:19:26 +0200 Subject: [PATCH 2/4] Add Arbitrary instance for RationalRect --- tests/Instances.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/tests/Instances.hs b/tests/Instances.hs index 6e74546533..d893b6bd1c 100644 --- a/tests/Instances.hs +++ b/tests/Instances.hs @@ -122,6 +122,10 @@ instance Arbitrary RectC where instance Arbitrary Rectangle where arbitrary = Rectangle <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary +instance Arbitrary RationalRect where + arbitrary = RationalRect <$> dim <*> dim <*> dim <*> dim + where + dim = arbitrary `suchThat` liftM2 (&&) (>= 0) (<= 1) newtype SizedPositive = SizedPositive Int deriving (Eq, Ord, Show, Read) From ad58f0a3880e694c3017acca873023fc00c6da6d Mon Sep 17 00:00:00 2001 From: slotThe Date: Fri, 16 Jul 2021 21:21:33 +0200 Subject: [PATCH 3/4] X.L.NoBorders: Add property test for OnlyFloat OnlyFloat should remove all floating borders at all times; this is a property that's readily tested with the multihead setup that's already defined. --- tests/NoBorders.hs | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/tests/NoBorders.hs b/tests/NoBorders.hs index 7e19230ee3..3296a258ad 100644 --- a/tests/NoBorders.hs +++ b/tests/NoBorders.hs @@ -1,13 +1,17 @@ +{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -Wall #-} module NoBorders where +import Instances () import Test.Hspec +import Test.Hspec.QuickCheck import qualified Data.Map as M import XMonad hiding (Screen) import qualified XMonad.Layout.NoBorders as NB +import XMonad.Prelude import XMonad.StackSet spec :: Spec @@ -39,6 +43,27 @@ spec = do NB.hiddens amb ws r1 s1 [] `shouldBe` [1] it "removes border on visible screen" $ do NB.hiddens amb ws r2 s2 [] `shouldBe` [2] + prop "prop_OnlyFloat" prop_OnlyFloat + +-- | All floating windows should be borderless. +prop_OnlyFloat + :: [Window] -- ^ Windows on the first monitor + -> [Window] -- ^ Windows on the second monitor + -> [RationalRect] -- ^ Floating window rectangles + -> Bool -- ^ Whether to consider focused or visible screen + -> Bool +prop_OnlyFloat (nub -> w1) (nub -> w2) frs b + = sort (w `intersect` map fst floats) + == sort (NB.hiddens NB.OnlyFloat ws r (differentiate w) []) + where + (w, w', r) = if b then (w1, w2, r1) else (w2, w1, r2) + ws = wsDualHead (differentiate w1) (differentiate w2) floats + floats = zip (interleave w w') frs + + interleave :: [a] -> [a] -> [a] + interleave (x : xs) (y : ys) = x : y : interleave xs ys + interleave [] ys = ys + interleave xs [] = xs -- +------+------+ -- | r1 | r2 | From 03f055fe0dfc2d0b20b977d919286184e4a35c02 Mon Sep 17 00:00:00 2001 From: slotThe Date: Fri, 16 Jul 2021 13:53:28 +0200 Subject: [PATCH 4/4] Updates CHANGES.md: Add OnlyFloat --- CHANGES.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/CHANGES.md b/CHANGES.md index 6c66749e7c..3cae808e51 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -573,6 +573,9 @@ - Fixed handling of floating window borders in multihead setups that was broken since 0.14. + + - Added `OnlyFloat` constructor to `Ambiguity` to unconditionally + remove all borders on floating windows. * `XMonad.Hooks.UrgencyHook`