{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
{-# OPTIONS_GHC -Wno-dodgy-imports #-}
module XMonad.Layout.NoBorders (
noBorders
, smartBorders
, withBorder
, lessBorders
, hasBorder
, SetsAmbiguous(..)
, Ambiguity(..)
, With(..)
, BorderMessage (..), borderEventHook
, SmartBorder, WithBorder, ConfigurableBorder
) where
import XMonad
import XMonad.Prelude hiding (singleton)
import XMonad.Layout.LayoutModifier
import qualified XMonad.StackSet as W
import qualified XMonad.Util.Rectangle as R
import qualified Data.Map as M
data WithBorder a = WithBorder Dimension [a] deriving ( ReadPrec [WithBorder a]
ReadPrec (WithBorder a)
Int -> ReadS (WithBorder a)
ReadS [WithBorder a]
(Int -> ReadS (WithBorder a))
-> ReadS [WithBorder a]
-> ReadPrec (WithBorder a)
-> ReadPrec [WithBorder a]
-> Read (WithBorder a)
forall a. Read a => ReadPrec [WithBorder a]
forall a. Read a => ReadPrec (WithBorder a)
forall a. Read a => Int -> ReadS (WithBorder a)
forall a. Read a => ReadS [WithBorder a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (WithBorder a)
readsPrec :: Int -> ReadS (WithBorder a)
$creadList :: forall a. Read a => ReadS [WithBorder a]
readList :: ReadS [WithBorder a]
$creadPrec :: forall a. Read a => ReadPrec (WithBorder a)
readPrec :: ReadPrec (WithBorder a)
$creadListPrec :: forall a. Read a => ReadPrec [WithBorder a]
readListPrec :: ReadPrec [WithBorder a]
Read, Int -> WithBorder a -> ShowS
[WithBorder a] -> ShowS
WithBorder a -> String
(Int -> WithBorder a -> ShowS)
-> (WithBorder a -> String)
-> ([WithBorder a] -> ShowS)
-> Show (WithBorder a)
forall a. Show a => Int -> WithBorder a -> ShowS
forall a. Show a => [WithBorder a] -> ShowS
forall a. Show a => WithBorder a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> WithBorder a -> ShowS
showsPrec :: Int -> WithBorder a -> ShowS
$cshow :: forall a. Show a => WithBorder a -> String
show :: WithBorder a -> String
$cshowList :: forall a. Show a => [WithBorder a] -> ShowS
showList :: [WithBorder a] -> ShowS
Show )
instance LayoutModifier WithBorder Window where
unhook :: WithBorder Window -> X ()
unhook (WithBorder Dimension
_ [Window]
s) = (XConf -> Dimension) -> X Dimension
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> Dimension
forall (l :: * -> *). XConfig l -> Dimension
borderWidth (XConfig Layout -> Dimension)
-> (XConf -> XConfig Layout) -> XConf -> Dimension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config) X Dimension -> (Dimension -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Window] -> Dimension -> X ()
setBorders [Window]
s
redoLayout :: WithBorder Window
-> Rectangle
-> Maybe (Stack Window)
-> [(Window, Rectangle)]
-> X ([(Window, Rectangle)], Maybe (WithBorder Window))
redoLayout (WithBorder Dimension
n [Window]
s) Rectangle
_ Maybe (Stack Window)
_ [(Window, Rectangle)]
wrs = do
(XConf -> Dimension) -> X Dimension
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> Dimension
forall (l :: * -> *). XConfig l -> Dimension
borderWidth (XConfig Layout -> Dimension)
-> (XConf -> XConfig Layout) -> XConf -> Dimension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config) X Dimension -> (Dimension -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Window] -> Dimension -> X ()
setBorders ([Window]
s [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Window]
ws)
[Window] -> Dimension -> X ()
setBorders [Window]
ws Dimension
n
([(Window, Rectangle)], Maybe (WithBorder Window))
-> X ([(Window, Rectangle)], Maybe (WithBorder Window))
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Window, Rectangle)]
wrs, WithBorder Window -> Maybe (WithBorder Window)
forall a. a -> Maybe a
Just (WithBorder Window -> Maybe (WithBorder Window))
-> WithBorder Window -> Maybe (WithBorder Window)
forall a b. (a -> b) -> a -> b
$ Dimension -> [Window] -> WithBorder Window
forall a. Dimension -> [a] -> WithBorder a
WithBorder Dimension
n [Window]
ws)
where
ws :: [Window]
ws = ((Window, Rectangle) -> Window)
-> [(Window, Rectangle)] -> [Window]
forall a b. (a -> b) -> [a] -> [b]
map (Window, Rectangle) -> Window
forall a b. (a, b) -> a
fst [(Window, Rectangle)]
wrs
noBorders :: LayoutClass l Window => l Window -> ModifiedLayout WithBorder l Window
noBorders :: forall (l :: * -> *).
LayoutClass l Window =>
l Window -> ModifiedLayout WithBorder l Window
noBorders = Dimension -> l Window -> ModifiedLayout WithBorder l Window
forall (l :: * -> *) a.
LayoutClass l a =>
Dimension -> l a -> ModifiedLayout WithBorder l a
withBorder Dimension
0
withBorder :: LayoutClass l a => Dimension -> l a -> ModifiedLayout WithBorder l a
withBorder :: forall (l :: * -> *) a.
LayoutClass l a =>
Dimension -> l a -> ModifiedLayout WithBorder l a
withBorder Dimension
b = WithBorder a -> l a -> ModifiedLayout WithBorder l a
forall (m :: * -> *) (l :: * -> *) a.
m a -> l a -> ModifiedLayout m l a
ModifiedLayout (WithBorder a -> l a -> ModifiedLayout WithBorder l a)
-> WithBorder a -> l a -> ModifiedLayout WithBorder l a
forall a b. (a -> b) -> a -> b
$ Dimension -> [a] -> WithBorder a
forall a. Dimension -> [a] -> WithBorder a
WithBorder Dimension
b []
setBorders :: [Window] -> Dimension -> X ()
setBorders :: [Window] -> Dimension -> X ()
setBorders [Window]
ws Dimension
bw = (Display -> X ()) -> X ()
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X ()) -> X ()) -> (Display -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Display
d -> (Window -> X ()) -> [Window] -> X ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\Window
w -> IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display -> Window -> Dimension -> IO ()
setWindowBorderWidth Display
d Window
w Dimension
bw) [Window]
ws
singleton :: [a] -> Bool
singleton :: forall a. [a] -> Bool
singleton = [a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([a] -> Bool) -> ([a] -> [a]) -> [a] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
1
type SmartBorder = ConfigurableBorder Ambiguity
smartBorders :: LayoutClass l a => l a -> ModifiedLayout SmartBorder l a
smartBorders :: forall (l :: * -> *) a.
LayoutClass l a =>
l a -> ModifiedLayout SmartBorder l a
smartBorders = Ambiguity -> l a -> ModifiedLayout SmartBorder l a
forall p (l :: * -> *) a.
(SetsAmbiguous p, Read p, Show p, LayoutClass l a) =>
p -> l a -> ModifiedLayout (ConfigurableBorder p) l a
lessBorders Ambiguity
Never
lessBorders :: (SetsAmbiguous p, Read p, Show p, LayoutClass l a) =>
p -> l a -> ModifiedLayout (ConfigurableBorder p) l a
lessBorders :: forall p (l :: * -> *) a.
(SetsAmbiguous p, Read p, Show p, LayoutClass l a) =>
p -> l a -> ModifiedLayout (ConfigurableBorder p) l a
lessBorders p
amb = ConfigurableBorder p a
-> l a -> ModifiedLayout (ConfigurableBorder p) l a
forall (m :: * -> *) (l :: * -> *) a.
m a -> l a -> ModifiedLayout m l a
ModifiedLayout (p -> [a] -> [a] -> [a] -> ConfigurableBorder p a
forall p w. p -> [w] -> [w] -> [w] -> ConfigurableBorder p w
ConfigurableBorder p
amb [] [] [])
hasBorder :: Bool -> ManageHook
hasBorder :: Bool -> Query (Endo WindowSet)
hasBorder Bool
b = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall a b. Query a -> (a -> Query b) -> Query b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X () -> Query ()
forall a. X a -> Query a
liftX (BorderMessage -> X ()
forall a. Message a => a -> X ()
broadcastMessage (BorderMessage -> X ()) -> BorderMessage -> X ()
forall a b. (a -> b) -> a -> b
$ Bool -> Window -> BorderMessage
HasBorder Bool
b Window
w) Query () -> Query (Endo WindowSet) -> Query (Endo WindowSet)
forall a b. Query a -> Query b -> Query b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Query (Endo WindowSet)
forall m. Monoid m => m
idHook
data BorderMessage
= HasBorder Bool Window
| ResetBorder Window
instance Message BorderMessage
data ConfigurableBorder p w = ConfigurableBorder
{ forall p w. ConfigurableBorder p w -> p
_generateHidden :: p
, forall p w. ConfigurableBorder p w -> [w]
alwaysHidden :: [w]
, forall p w. ConfigurableBorder p w -> [w]
neverHidden :: [w]
, forall p w. ConfigurableBorder p w -> [w]
currentHidden :: [w]
} deriving (ReadPrec [ConfigurableBorder p w]
ReadPrec (ConfigurableBorder p w)
Int -> ReadS (ConfigurableBorder p w)
ReadS [ConfigurableBorder p w]
(Int -> ReadS (ConfigurableBorder p w))
-> ReadS [ConfigurableBorder p w]
-> ReadPrec (ConfigurableBorder p w)
-> ReadPrec [ConfigurableBorder p w]
-> Read (ConfigurableBorder p w)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall p w. (Read p, Read w) => ReadPrec [ConfigurableBorder p w]
forall p w. (Read p, Read w) => ReadPrec (ConfigurableBorder p w)
forall p w.
(Read p, Read w) =>
Int -> ReadS (ConfigurableBorder p w)
forall p w. (Read p, Read w) => ReadS [ConfigurableBorder p w]
$creadsPrec :: forall p w.
(Read p, Read w) =>
Int -> ReadS (ConfigurableBorder p w)
readsPrec :: Int -> ReadS (ConfigurableBorder p w)
$creadList :: forall p w. (Read p, Read w) => ReadS [ConfigurableBorder p w]
readList :: ReadS [ConfigurableBorder p w]
$creadPrec :: forall p w. (Read p, Read w) => ReadPrec (ConfigurableBorder p w)
readPrec :: ReadPrec (ConfigurableBorder p w)
$creadListPrec :: forall p w. (Read p, Read w) => ReadPrec [ConfigurableBorder p w]
readListPrec :: ReadPrec [ConfigurableBorder p w]
Read, Int -> ConfigurableBorder p w -> ShowS
[ConfigurableBorder p w] -> ShowS
ConfigurableBorder p w -> String
(Int -> ConfigurableBorder p w -> ShowS)
-> (ConfigurableBorder p w -> String)
-> ([ConfigurableBorder p w] -> ShowS)
-> Show (ConfigurableBorder p w)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall p w.
(Show p, Show w) =>
Int -> ConfigurableBorder p w -> ShowS
forall p w. (Show p, Show w) => [ConfigurableBorder p w] -> ShowS
forall p w. (Show p, Show w) => ConfigurableBorder p w -> String
$cshowsPrec :: forall p w.
(Show p, Show w) =>
Int -> ConfigurableBorder p w -> ShowS
showsPrec :: Int -> ConfigurableBorder p w -> ShowS
$cshow :: forall p w. (Show p, Show w) => ConfigurableBorder p w -> String
show :: ConfigurableBorder p w -> String
$cshowList :: forall p w. (Show p, Show w) => [ConfigurableBorder p w] -> ShowS
showList :: [ConfigurableBorder p w] -> ShowS
Show)
borderEventHook :: Event -> X All
borderEventHook :: Event -> X All
borderEventHook DestroyWindowEvent{ ev_window :: Event -> Window
ev_window = Window
w } = do
BorderMessage -> X ()
forall a. Message a => a -> X ()
broadcastMessage (BorderMessage -> X ()) -> BorderMessage -> X ()
forall a b. (a -> b) -> a -> b
$ Window -> BorderMessage
ResetBorder Window
w
All -> X All
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return (All -> X All) -> All -> X All
forall a b. (a -> b) -> a -> b
$ Bool -> All
All Bool
True
borderEventHook Event
_ = All -> X All
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return (All -> X All) -> All -> X All
forall a b. (a -> b) -> a -> b
$ Bool -> All
All Bool
True
instance (Read p, Show p, SetsAmbiguous p) => LayoutModifier (ConfigurableBorder p) Window where
unhook :: ConfigurableBorder p Window -> X ()
unhook (ConfigurableBorder p
_ [Window]
_ [Window]
_ [Window]
ch) = (XConf -> Dimension) -> X Dimension
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> Dimension
forall (l :: * -> *). XConfig l -> Dimension
borderWidth (XConfig Layout -> Dimension)
-> (XConf -> XConfig Layout) -> XConf -> Dimension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config) X Dimension -> (Dimension -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Window] -> Dimension -> X ()
setBorders [Window]
ch
redoLayout :: ConfigurableBorder p Window
-> Rectangle
-> Maybe (Stack Window)
-> [(Window, Rectangle)]
-> X ([(Window, Rectangle)], Maybe (ConfigurableBorder p Window))
redoLayout cb :: ConfigurableBorder p Window
cb@(ConfigurableBorder p
gh [Window]
ah [Window]
nh [Window]
ch) Rectangle
lr Maybe (Stack Window)
mst [(Window, Rectangle)]
wrs = do
let gh' :: WindowSet -> m [Window]
gh' WindowSet
wset = let lh :: [Window]
lh = p
-> WindowSet
-> Rectangle
-> Maybe (Stack Window)
-> [(Window, Rectangle)]
-> [Window]
forall p.
SetsAmbiguous p =>
p
-> WindowSet
-> Rectangle
-> Maybe (Stack Window)
-> [(Window, Rectangle)]
-> [Window]
hiddens p
gh WindowSet
wset Rectangle
lr Maybe (Stack Window)
mst [(Window, Rectangle)]
wrs
in [Window] -> m [Window]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Window] -> m [Window]) -> [Window] -> m [Window]
forall a b. (a -> b) -> a -> b
$ ([Window]
ah [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
`union` [Window]
lh) [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Window]
nh
[Window]
ch' <- (WindowSet -> X [Window]) -> X [Window]
forall a. (WindowSet -> X a) -> X a
withWindowSet WindowSet -> X [Window]
forall {m :: * -> *}. Monad m => WindowSet -> m [Window]
gh'
(XConf -> Dimension) -> X Dimension
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> Dimension
forall (l :: * -> *). XConfig l -> Dimension
borderWidth (XConfig Layout -> Dimension)
-> (XConf -> XConfig Layout) -> XConf -> Dimension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config) X Dimension -> (Dimension -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Window] -> Dimension -> X ()
setBorders ([Window]
ch [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Window]
ch')
[Window] -> Dimension -> X ()
setBorders [Window]
ch' Dimension
0
([(Window, Rectangle)], Maybe (ConfigurableBorder p Window))
-> X ([(Window, Rectangle)], Maybe (ConfigurableBorder p Window))
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Window, Rectangle)]
wrs, ConfigurableBorder p Window -> Maybe (ConfigurableBorder p Window)
forall a. a -> Maybe a
Just (ConfigurableBorder p Window
-> Maybe (ConfigurableBorder p Window))
-> ConfigurableBorder p Window
-> Maybe (ConfigurableBorder p Window)
forall a b. (a -> b) -> a -> b
$ ConfigurableBorder p Window
cb { currentHidden = ch' })
pureMess :: ConfigurableBorder p Window
-> SomeMessage -> Maybe (ConfigurableBorder p Window)
pureMess cb :: ConfigurableBorder p Window
cb@(ConfigurableBorder p
gh [Window]
ah [Window]
nh [Window]
ch) SomeMessage
m
| Just (HasBorder Bool
b Window
w) <- SomeMessage -> Maybe BorderMessage
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m =
let consNewIf :: [Window] -> Bool -> Maybe [Window]
consNewIf [Window]
l Bool
True = if Window
w Window -> [Window] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Window]
l then Maybe [Window]
forall a. Maybe a
Nothing else [Window] -> Maybe [Window]
forall a. a -> Maybe a
Just (Window
wWindow -> [Window] -> [Window]
forall a. a -> [a] -> [a]
:[Window]
l)
consNewIf [Window]
l Bool
False = [Window] -> Maybe [Window]
forall a. a -> Maybe a
Just [Window]
l
in p
-> [Window] -> [Window] -> [Window] -> ConfigurableBorder p Window
forall p w. p -> [w] -> [w] -> [w] -> ConfigurableBorder p w
ConfigurableBorder p
gh ([Window] -> [Window] -> [Window] -> ConfigurableBorder p Window)
-> Maybe [Window]
-> Maybe ([Window] -> [Window] -> ConfigurableBorder p Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Window] -> Bool -> Maybe [Window]
consNewIf [Window]
ah (Bool -> Bool
not Bool
b)
Maybe ([Window] -> [Window] -> ConfigurableBorder p Window)
-> Maybe [Window]
-> Maybe ([Window] -> ConfigurableBorder p Window)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Window] -> Bool -> Maybe [Window]
consNewIf [Window]
nh Bool
b
Maybe ([Window] -> ConfigurableBorder p Window)
-> Maybe [Window] -> Maybe (ConfigurableBorder p Window)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Window] -> Maybe [Window]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Window]
ch
| Just (ResetBorder Window
w) <- SomeMessage -> Maybe BorderMessage
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m =
let delete' :: a -> [a] -> (Bool, [a])
delete' a
e [a]
l = if a
e a -> [a] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
l then (Bool
True,a -> [a] -> [a]
forall a. Eq a => a -> [a] -> [a]
delete a
e [a]
l) else (Bool
False,[a]
l)
(Bool
da,[Window]
ah') = Window -> [Window] -> (Bool, [Window])
forall {a}. Eq a => a -> [a] -> (Bool, [a])
delete' Window
w [Window]
ah
(Bool
dn,[Window]
nh') = Window -> [Window] -> (Bool, [Window])
forall {a}. Eq a => a -> [a] -> (Bool, [a])
delete' Window
w [Window]
nh
in if Bool
da Bool -> Bool -> Bool
|| Bool
dn
then ConfigurableBorder p Window -> Maybe (ConfigurableBorder p Window)
forall a. a -> Maybe a
Just ConfigurableBorder p Window
cb { alwaysHidden = ah', neverHidden = nh' }
else Maybe (ConfigurableBorder p Window)
forall a. Maybe a
Nothing
| Bool
otherwise = Maybe (ConfigurableBorder p Window)
forall a. Maybe a
Nothing
class SetsAmbiguous p where
hiddens :: p -> WindowSet -> Rectangle -> Maybe (W.Stack Window) -> [(Window, Rectangle)] -> [Window]
instance SetsAmbiguous Ambiguity where
hiddens :: Ambiguity
-> WindowSet
-> Rectangle
-> Maybe (Stack Window)
-> [(Window, Rectangle)]
-> [Window]
hiddens Ambiguity
amb WindowSet
wset Rectangle
lr Maybe (Stack Window)
mst [(Window, Rectangle)]
wrs
| Combine With
Union Ambiguity
a Ambiguity
b <- Ambiguity
amb = ([Window] -> [Window] -> [Window])
-> (Ambiguity -> [Window]) -> Ambiguity -> Ambiguity -> [Window]
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
union Ambiguity -> [Window]
forall {p}. SetsAmbiguous p => p -> [Window]
next Ambiguity
a Ambiguity
b
| Combine With
Difference Ambiguity
a Ambiguity
b <- Ambiguity
amb = ([Window] -> [Window] -> [Window])
-> (Ambiguity -> [Window]) -> Ambiguity -> Ambiguity -> [Window]
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
(\\) Ambiguity -> [Window]
forall {p}. SetsAmbiguous p => p -> [Window]
next Ambiguity
a Ambiguity
b
| Combine With
Intersection Ambiguity
a Ambiguity
b <- Ambiguity
amb = ([Window] -> [Window] -> [Window])
-> (Ambiguity -> [Window]) -> Ambiguity -> Ambiguity -> [Window]
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
intersect Ambiguity -> [Window]
forall {p}. SetsAmbiguous p => p -> [Window]
next Ambiguity
a Ambiguity
b
| Bool
otherwise = [Window] -> [Window]
forall {a}. [a] -> [a]
tiled [Window]
ms [Window] -> [Window] -> [Window]
forall a. [a] -> [a] -> [a]
++ [Window]
floating
where next :: p -> [Window]
next p
p = p
-> WindowSet
-> Rectangle
-> Maybe (Stack Window)
-> [(Window, Rectangle)]
-> [Window]
forall p.
SetsAmbiguous p =>
p
-> WindowSet
-> Rectangle
-> Maybe (Stack Window)
-> [(Window, Rectangle)]
-> [Window]
hiddens p
p WindowSet
wset Rectangle
lr Maybe (Stack Window)
mst [(Window, Rectangle)]
wrs
screens :: [Screen String (Layout Window) Window ScreenId ScreenDetail]
screens = [ Screen String (Layout Window) Window ScreenId ScreenDetail
scr | Screen String (Layout Window) Window ScreenId ScreenDetail
scr <- WindowSet
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall i l a s sd. StackSet i l a s sd -> [Screen i l a s sd]
W.screens WindowSet
wset
, case Ambiguity
amb of
Ambiguity
Never -> Bool
True
Ambiguity
_ -> Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Window] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Window] -> Bool) -> [Window] -> Bool
forall a b. (a -> b) -> a -> b
$ Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window]
forall {i} {l} {a} {sid} {sd}. Screen i l a sid sd -> [a]
integrate Screen String (Layout Window) Window ScreenId ScreenDetail
scr
, Bool -> Bool
not (Bool -> Bool) -> (ScreenDetail -> Bool) -> ScreenDetail -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rectangle -> Bool
R.empty (Rectangle -> Bool)
-> (ScreenDetail -> Rectangle) -> ScreenDetail -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScreenDetail -> Rectangle
screenRect
(ScreenDetail -> Bool) -> ScreenDetail -> Bool
forall a b. (a -> b) -> a -> b
$ Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenDetail
forall i l a sid sd. Screen i l a sid sd -> sd
W.screenDetail Screen String (Layout Window) Window ScreenId ScreenDetail
scr
]
thisScreen :: [Screen String (Layout Window) Window ScreenId ScreenDetail]
thisScreen = [ Screen String (Layout Window) Window ScreenId ScreenDetail
scr | Screen String (Layout Window) Window ScreenId ScreenDetail
scr <- WindowSet
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall i l a s sd. StackSet i l a s sd -> [Screen i l a s sd]
W.screens WindowSet
wset
, ScreenDetail -> Rectangle
screenRect (Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenDetail
forall i l a sid sd. Screen i l a sid sd -> sd
W.screenDetail Screen String (Layout Window) Window ScreenId ScreenDetail
scr) Rectangle -> Rectangle -> Bool
`R.supersetOf` Rectangle
lr ]
floating :: [Window]
floating = do
Screen String (Layout Window) Window ScreenId ScreenDetail
scr <- [Screen String (Layout Window) Window ScreenId ScreenDetail]
thisScreen
let wz :: Integer -> (Window,Rectangle)
-> (Integer,Window,Rectangle)
wz :: Integer -> (Window, Rectangle) -> (Integer, Window, Rectangle)
wz Integer
i (Window
w,Rectangle
wr) = (Integer
i,Window
w,Rectangle
wr)
ts :: [(Integer, Window, Rectangle)]
ts = [(Integer, Window, Rectangle)] -> [(Integer, Window, Rectangle)]
forall {a}. [a] -> [a]
reverse ([(Integer, Window, Rectangle)] -> [(Integer, Window, Rectangle)])
-> ([(Window, Rectangle)] -> [(Integer, Window, Rectangle)])
-> [(Window, Rectangle)]
-> [(Integer, Window, Rectangle)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Integer -> (Window, Rectangle) -> (Integer, Window, Rectangle))
-> [Integer]
-> [(Window, Rectangle)]
-> [(Integer, Window, Rectangle)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Integer -> (Window, Rectangle) -> (Integer, Window, Rectangle)
wz [-Integer
1,-Integer
2..] ([(Window, Rectangle)] -> [(Integer, Window, Rectangle)])
-> [(Window, Rectangle)] -> [(Integer, Window, Rectangle)]
forall a b. (a -> b) -> a -> b
$ [(Window, Rectangle)]
wrs
fs :: [(Integer, Window, Rectangle)]
fs = (Integer -> (Window, Rectangle) -> (Integer, Window, Rectangle))
-> [Integer]
-> [(Window, Rectangle)]
-> [(Integer, Window, Rectangle)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Integer -> (Window, Rectangle) -> (Integer, Window, Rectangle)
wz [Integer
0..] ([(Window, Rectangle)] -> [(Integer, Window, Rectangle)])
-> [(Window, Rectangle)] -> [(Integer, Window, Rectangle)]
forall a b. (a -> b) -> a -> b
$ do
Window
w <- [Window] -> [Window]
forall {a}. [a] -> [a]
reverse ([Window] -> [Window])
-> (Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window])
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Stack Window) -> [Window]
forall a. Maybe (Stack a) -> [a]
W.integrate' (Maybe (Stack Window) -> [Window])
-> (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Maybe (Stack Window))
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Workspace String (Layout Window) Window -> Maybe (Stack Window)
forall i l a. Workspace i l a -> Maybe (Stack a)
W.stack (Workspace String (Layout Window) Window -> Maybe (Stack Window))
-> (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window)
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> Maybe (Stack Window)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
W.workspace (Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window])
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window]
forall a b. (a -> b) -> a -> b
$ Screen String (Layout Window) Window ScreenId ScreenDetail
scr
Just RationalRect
wr <- [Window -> Map Window RationalRect -> Maybe RationalRect
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Window
w (WindowSet -> Map Window RationalRect
forall i l a sid sd. StackSet i l a sid sd -> Map a RationalRect
W.floating WindowSet
wset)]
(Window, Rectangle) -> [(Window, Rectangle)]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (Window
w,Rectangle -> RationalRect -> Rectangle
scaleRationalRect Rectangle
sr RationalRect
wr)
sr :: Rectangle
sr = ScreenDetail -> Rectangle
screenRect (ScreenDetail -> Rectangle)
-> (Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenDetail)
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> Rectangle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenDetail
forall i l a sid sd. Screen i l a sid sd -> sd
W.screenDetail (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Rectangle)
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> Rectangle
forall a b. (a -> b) -> a -> b
$ Screen String (Layout Window) Window ScreenId ScreenDetail
scr
(Integer
i1,Window
w1,Rectangle
wr1) <- [(Integer, Window, Rectangle)]
fs
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> [()]) -> Bool -> [()]
forall a b. (a -> b) -> a -> b
$ case Ambiguity
amb of
Ambiguity
OnlyLayoutFloatBelow ->
let vu :: [Bool]
vu = do
Rectangle
gr <- Rectangle
sr Rectangle -> Rectangle -> [Rectangle]
`R.difference` Rectangle
lr
(Integer
i2,Window
_w2,Rectangle
wr2) <- [(Integer, Window, Rectangle)]
ts [(Integer, Window, Rectangle)]
-> [(Integer, Window, Rectangle)] -> [(Integer, Window, Rectangle)]
forall a. [a] -> [a] -> [a]
++ [(Integer, Window, Rectangle)]
fs
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> [()]) -> Bool -> [()]
forall a b. (a -> b) -> a -> b
$ Integer
i2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
i1
[Rectangle
wr2 Rectangle -> Rectangle -> Bool
`R.intersects` Rectangle
gr]
in Rectangle
lr Rectangle -> Rectangle -> Bool
forall a. Eq a => a -> a -> Bool
== Rectangle
wr1 Bool -> Bool -> Bool
&& (Bool -> Bool
not (Bool -> Bool) -> ([Bool] -> Bool) -> [Bool] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or) [Bool]
vu
Ambiguity
OnlyLayoutFloat ->
Rectangle
lr Rectangle -> Rectangle -> Bool
forall a. Eq a => a -> a -> Bool
== Rectangle
wr1
Ambiguity
OnlyFloat ->
Bool
True
Ambiguity
_ ->
Rectangle
wr1 Rectangle -> Rectangle -> Bool
`R.supersetOf` Rectangle
sr
Window -> [Window]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return Window
w1
ms :: [Window]
ms = (Window -> Bool) -> [Window] -> [Window]
forall a. (a -> Bool) -> [a] -> [a]
filter (Window -> [Window] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Maybe (Stack Window) -> [Window]
forall a. Maybe (Stack a) -> [a]
W.integrate' Maybe (Stack Window)
mst) ([Window] -> [Window]) -> [Window] -> [Window]
forall a b. (a -> b) -> a -> b
$ ((Window, Rectangle) -> Window)
-> [(Window, Rectangle)] -> [Window]
forall a b. (a -> b) -> [a] -> [b]
map (Window, Rectangle) -> Window
forall a b. (a, b) -> a
fst [(Window, Rectangle)]
wrs
tiled :: [a] -> [a]
tiled [a
w]
| Ambiguity
Screen <- Ambiguity
amb = [a
w]
| Ambiguity
OnlyScreenFloat <- Ambiguity
amb = []
| Ambiguity
OnlyLayoutFloat <- Ambiguity
amb = []
| Ambiguity
OnlyFloat <- Ambiguity
amb = []
| Ambiguity
OnlyLayoutFloatBelow <- Ambiguity
amb = []
| Ambiguity
OtherIndicated <- Ambiguity
amb
, let nonF :: [[Window]]
nonF = (Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window])
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [[Window]]
forall a b. (a -> b) -> [a] -> [b]
map Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window]
forall {i} {l} {a} {sid} {sd}. Screen i l a sid sd -> [a]
integrate ([Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [[Window]])
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [[Window]]
forall a b. (a -> b) -> a -> b
$ WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
W.current WindowSet
wset Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a. a -> [a] -> [a]
: WindowSet
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall i l a s sd. StackSet i l a s sd -> [Screen i l a s sd]
W.visible WindowSet
wset
, [Window] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([[Window]] -> [Window]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Window]]
nonF) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> [(Window, Rectangle)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Window, Rectangle)]
wrs
, [Int] -> Bool
forall a. [a] -> Bool
singleton ([Int] -> Bool) -> [Int] -> Bool
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int
1Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==) ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ ([Window] -> Int) -> [[Window]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [Window] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Window]]
nonF = [a
w]
| [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> Bool
forall a. [a] -> Bool
singleton [Screen String (Layout Window) Window ScreenId ScreenDetail]
screens = [a
w]
tiled [a]
_ = []
integrate :: Screen i l a sid sd -> [a]
integrate Screen i l a sid sd
y = Maybe (Stack a) -> [a]
forall a. Maybe (Stack a) -> [a]
W.integrate' (Maybe (Stack a) -> [a])
-> (Workspace i l a -> Maybe (Stack a)) -> Workspace i l a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Workspace i l a -> Maybe (Stack a)
forall i l a. Workspace i l a -> Maybe (Stack a)
W.stack (Workspace i l a -> [a]) -> Workspace i l a -> [a]
forall a b. (a -> b) -> a -> b
$ Screen i l a sid sd -> Workspace i l a
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
W.workspace Screen i l a sid sd
y
data Ambiguity
= Combine With Ambiguity Ambiguity
| OnlyLayoutFloatBelow
| OnlyLayoutFloat
| OnlyScreenFloat
| Never
| EmptyScreen
| OtherIndicated
| OnlyFloat
| Screen
deriving (ReadPrec [Ambiguity]
ReadPrec Ambiguity
Int -> ReadS Ambiguity
ReadS [Ambiguity]
(Int -> ReadS Ambiguity)
-> ReadS [Ambiguity]
-> ReadPrec Ambiguity
-> ReadPrec [Ambiguity]
-> Read Ambiguity
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Ambiguity
readsPrec :: Int -> ReadS Ambiguity
$creadList :: ReadS [Ambiguity]
readList :: ReadS [Ambiguity]
$creadPrec :: ReadPrec Ambiguity
readPrec :: ReadPrec Ambiguity
$creadListPrec :: ReadPrec [Ambiguity]
readListPrec :: ReadPrec [Ambiguity]
Read, Int -> Ambiguity -> ShowS
[Ambiguity] -> ShowS
Ambiguity -> String
(Int -> Ambiguity -> ShowS)
-> (Ambiguity -> String)
-> ([Ambiguity] -> ShowS)
-> Show Ambiguity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ambiguity -> ShowS
showsPrec :: Int -> Ambiguity -> ShowS
$cshow :: Ambiguity -> String
show :: Ambiguity -> String
$cshowList :: [Ambiguity] -> ShowS
showList :: [Ambiguity] -> ShowS
Show)
data With = Union
| Difference
| Intersection
deriving (ReadPrec [With]
ReadPrec With
Int -> ReadS With
ReadS [With]
(Int -> ReadS With)
-> ReadS [With] -> ReadPrec With -> ReadPrec [With] -> Read With
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS With
readsPrec :: Int -> ReadS With
$creadList :: ReadS [With]
readList :: ReadS [With]
$creadPrec :: ReadPrec With
readPrec :: ReadPrec With
$creadListPrec :: ReadPrec [With]
readListPrec :: ReadPrec [With]
Read, Int -> With -> ShowS
[With] -> ShowS
With -> String
(Int -> With -> ShowS)
-> (With -> String) -> ([With] -> ShowS) -> Show With
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> With -> ShowS
showsPrec :: Int -> With -> ShowS
$cshow :: With -> String
show :: With -> String
$cshowList :: [With] -> ShowS
showList :: [With] -> ShowS
Show)