{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
module XMonad.Layout.LayoutScreens (
layoutScreens, layoutSplitScreen, fixedLayout,
FixedLayout,
) where
import XMonad
import qualified XMonad.StackSet as W
layoutScreens :: LayoutClass l Int => Int -> l Int -> X ()
layoutScreens :: Int -> l Int -> X ()
layoutScreens Int
nscr l Int
_ | Int
nscr Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = String -> X ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> X ()) -> String -> X ()
forall a b. (a -> b) -> a -> b
$ String
"Can't layoutScreens with only " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
nscr String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" screens."
layoutScreens Int
nscr l Int
l =
do Rectangle
rtrect <- (XConf -> Window) -> X Window
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Window
theRoot X Window -> (Window -> X Rectangle) -> X Rectangle
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Window -> X Rectangle
getWindowRectangle
([(Int, Rectangle)]
wss, Maybe (l Int)
_) <- Workspace String (l Int) Int
-> Rectangle -> X ([(Int, Rectangle)], Maybe (l Int))
forall (layout :: * -> *) a.
LayoutClass layout a =>
Workspace String (layout a) a
-> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
runLayout (String
-> l Int -> Maybe (Stack Int) -> Workspace String (l Int) Int
forall i l a. i -> l -> Maybe (Stack a) -> Workspace i l a
W.Workspace String
"" l Int
l (Stack Int -> Maybe (Stack Int)
forall a. a -> Maybe a
Just (Stack Int -> Maybe (Stack Int)) -> Stack Int -> Maybe (Stack Int)
forall a b. (a -> b) -> a -> b
$ Stack :: forall a. a -> [a] -> [a] -> Stack a
W.Stack { focus :: Int
W.focus=Int
1, up :: [Int]
W.up=[],down :: [Int]
W.down=[Int
1..Int
nscrInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] })) Rectangle
rtrect
(WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WindowSet -> WindowSet) -> X ()
forall a b. (a -> b) -> a -> b
$ \ws :: WindowSet
ws@W.StackSet{ current :: forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
W.current = Screen String (Layout Window) Window ScreenId ScreenDetail
v, visible :: forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
W.visible = [Screen String (Layout Window) Window ScreenId ScreenDetail]
vs, hidden :: forall i l a sid sd. StackSet i l a sid sd -> [Workspace i l a]
W.hidden = [Workspace String (Layout Window) Window]
hs } ->
let (Workspace String (Layout Window) Window
x:[Workspace String (Layout Window) Window]
xs, [Workspace String (Layout Window) Window]
ys) = Int
-> [Workspace String (Layout Window) Window]
-> ([Workspace String (Layout Window) Window],
[Workspace String (Layout Window) Window])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
nscr ([Workspace String (Layout Window) Window]
-> ([Workspace String (Layout Window) Window],
[Workspace String (Layout Window) Window]))
-> [Workspace String (Layout Window) Window]
-> ([Workspace String (Layout Window) Window],
[Workspace String (Layout Window) Window])
forall a b. (a -> b) -> a -> b
$ (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window)
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [Workspace String (Layout Window) Window]
forall a b. (a -> b) -> [a] -> [b]
map 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
vScreen 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]
:[Screen String (Layout Window) Window ScreenId ScreenDetail]
vs) [Workspace String (Layout Window) Window]
-> [Workspace String (Layout Window) Window]
-> [Workspace String (Layout Window) Window]
forall a. [a] -> [a] -> [a]
++ [Workspace String (Layout Window) Window]
hs
Rectangle
s:[Rectangle]
ss = ((Int, Rectangle) -> Rectangle)
-> [(Int, Rectangle)] -> [Rectangle]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Rectangle) -> Rectangle
forall a b. (a, b) -> b
snd [(Int, Rectangle)]
wss
in WindowSet
ws { current :: Screen String (Layout Window) Window ScreenId ScreenDetail
W.current = Workspace String (Layout Window) Window
-> ScreenId
-> ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd.
Workspace i l a -> sid -> sd -> Screen i l a sid sd
W.Screen Workspace String (Layout Window) Window
x ScreenId
0 (Rectangle -> ScreenDetail
SD Rectangle
s)
, visible :: [Screen String (Layout Window) Window ScreenId ScreenDetail]
W.visible = (Workspace String (Layout Window) Window
-> ScreenId
-> ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> [Workspace String (Layout Window) Window]
-> [ScreenId]
-> [ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 Workspace String (Layout Window) Window
-> ScreenId
-> ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd.
Workspace i l a -> sid -> sd -> Screen i l a sid sd
W.Screen [Workspace String (Layout Window) Window]
xs [ScreenId
1 ..] ([ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail])
-> [ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a b. (a -> b) -> a -> b
$ (Rectangle -> ScreenDetail) -> [Rectangle] -> [ScreenDetail]
forall a b. (a -> b) -> [a] -> [b]
map Rectangle -> ScreenDetail
SD [Rectangle]
ss
, hidden :: [Workspace String (Layout Window) Window]
W.hidden = [Workspace String (Layout Window) Window]
ys }
layoutSplitScreen :: LayoutClass l Int => Int -> l Int -> X ()
layoutSplitScreen :: Int -> l Int -> X ()
layoutSplitScreen Int
nscr l Int
_ | Int
nscr Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = String -> X ()
forall (m :: * -> *). MonadIO m => String -> m ()
trace (String -> X ()) -> String -> X ()
forall a b. (a -> b) -> a -> b
$ String
"Can't layoutSplitScreen with only " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
nscr String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" screens."
layoutSplitScreen Int
nscr l Int
l =
do Rectangle
rect <- (XState -> Rectangle) -> X Rectangle
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets ((XState -> Rectangle) -> X Rectangle)
-> (XState -> Rectangle) -> X Rectangle
forall a b. (a -> b) -> a -> b
$ ScreenDetail -> Rectangle
screenRect (ScreenDetail -> Rectangle)
-> (XState -> ScreenDetail) -> XState -> 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
-> ScreenDetail)
-> (XState
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> XState
-> ScreenDetail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> (XState -> WindowSet)
-> XState
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XState -> WindowSet
windowset
([(Int, Rectangle)]
wss, Maybe (l Int)
_) <- Workspace String (l Int) Int
-> Rectangle -> X ([(Int, Rectangle)], Maybe (l Int))
forall (layout :: * -> *) a.
LayoutClass layout a =>
Workspace String (layout a) a
-> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
runLayout (String
-> l Int -> Maybe (Stack Int) -> Workspace String (l Int) Int
forall i l a. i -> l -> Maybe (Stack a) -> Workspace i l a
W.Workspace String
"" l Int
l (Stack Int -> Maybe (Stack Int)
forall a. a -> Maybe a
Just (Stack Int -> Maybe (Stack Int)) -> Stack Int -> Maybe (Stack Int)
forall a b. (a -> b) -> a -> b
$ Stack :: forall a. a -> [a] -> [a] -> Stack a
W.Stack { focus :: Int
W.focus=Int
1, up :: [Int]
W.up=[],down :: [Int]
W.down=[Int
1..Int
nscrInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] })) Rectangle
rect
(WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WindowSet -> WindowSet) -> X ()
forall a b. (a -> b) -> a -> b
$ \ws :: WindowSet
ws@W.StackSet{ current :: forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
W.current = Screen String (Layout Window) Window ScreenId ScreenDetail
c, visible :: forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
W.visible = [Screen String (Layout Window) Window ScreenId ScreenDetail]
vs, hidden :: forall i l a sid sd. StackSet i l a sid sd -> [Workspace i l a]
W.hidden = [Workspace String (Layout Window) Window]
hs } ->
let (Workspace String (Layout Window) Window
x:[Workspace String (Layout Window) Window]
xs, [Workspace String (Layout Window) Window]
ys) = Int
-> [Workspace String (Layout Window) Window]
-> ([Workspace String (Layout Window) Window],
[Workspace String (Layout Window) Window])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
nscr ([Workspace String (Layout Window) Window]
-> ([Workspace String (Layout Window) Window],
[Workspace String (Layout Window) Window]))
-> [Workspace String (Layout Window) Window]
-> ([Workspace String (Layout Window) Window],
[Workspace String (Layout Window) Window])
forall a b. (a -> b) -> a -> b
$ 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
c Workspace String (Layout Window) Window
-> [Workspace String (Layout Window) Window]
-> [Workspace String (Layout Window) Window]
forall a. a -> [a] -> [a]
: [Workspace String (Layout Window) Window]
hs
Rectangle
s:[Rectangle]
ss = ((Int, Rectangle) -> Rectangle)
-> [(Int, Rectangle)] -> [Rectangle]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Rectangle) -> Rectangle
forall a b. (a, b) -> b
snd [(Int, Rectangle)]
wss
in WindowSet
ws { current :: Screen String (Layout Window) Window ScreenId ScreenDetail
W.current = Workspace String (Layout Window) Window
-> ScreenId
-> ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd.
Workspace i l a -> sid -> sd -> Screen i l a sid sd
W.Screen Workspace String (Layout Window) Window
x (Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
W.screen Screen String (Layout Window) Window ScreenId ScreenDetail
c) (Rectangle -> ScreenDetail
SD Rectangle
s)
, visible :: [Screen String (Layout Window) Window ScreenId ScreenDetail]
W.visible = (Workspace String (Layout Window) Window
-> ScreenId
-> ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> [Workspace String (Layout Window) Window]
-> [ScreenId]
-> [ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 Workspace String (Layout Window) Window
-> ScreenId
-> ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd.
Workspace i l a -> sid -> sd -> Screen i l a sid sd
W.Screen [Workspace String (Layout Window) Window]
xs [(Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
W.screen Screen String (Layout Window) Window ScreenId ScreenDetail
cScreenId -> ScreenId -> ScreenId
forall a. Num a => a -> a -> a
+ScreenId
1) ..] ((Rectangle -> ScreenDetail) -> [Rectangle] -> [ScreenDetail]
forall a b. (a -> b) -> [a] -> [b]
map Rectangle -> ScreenDetail
SD [Rectangle]
ss) [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]
++
(Screen String (Layout Window) Window ScreenId ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a b. (a -> b) -> [a] -> [b]
map (\Screen String (Layout Window) Window ScreenId ScreenDetail
v -> if Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
W.screen Screen String (Layout Window) Window ScreenId ScreenDetail
vScreenId -> ScreenId -> Bool
forall a. Ord a => a -> a -> Bool
>Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
W.screen Screen String (Layout Window) Window ScreenId ScreenDetail
c then Screen String (Layout Window) Window ScreenId ScreenDetail
v{screen :: ScreenId
W.screen = Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
W.screen Screen String (Layout Window) Window ScreenId ScreenDetail
v ScreenId -> ScreenId -> ScreenId
forall a. Num a => a -> a -> a
+ Int -> ScreenId
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
nscrInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)} else Screen String (Layout Window) Window ScreenId ScreenDetail
v) [Screen String (Layout Window) Window ScreenId ScreenDetail]
vs
, hidden :: [Workspace String (Layout Window) Window]
W.hidden = [Workspace String (Layout Window) Window]
ys }
getWindowRectangle :: Window -> X Rectangle
getWindowRectangle :: Window -> X Rectangle
getWindowRectangle Window
w = (Display -> X Rectangle) -> X Rectangle
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X Rectangle) -> X Rectangle)
-> (Display -> X Rectangle) -> X Rectangle
forall a b. (a -> b) -> a -> b
$ \Display
d ->
do WindowAttributes
a <- IO WindowAttributes -> X WindowAttributes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO WindowAttributes -> X WindowAttributes)
-> IO WindowAttributes -> X WindowAttributes
forall a b. (a -> b) -> a -> b
$ Display -> Window -> IO WindowAttributes
getWindowAttributes Display
d Window
w
Rectangle -> X Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle -> X Rectangle) -> Rectangle -> X Rectangle
forall a b. (a -> b) -> a -> b
$ Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Position) -> CInt -> Position
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_x WindowAttributes
a) (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Position) -> CInt -> Position
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_y WindowAttributes
a)
(CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Dimension) -> CInt -> Dimension
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_width WindowAttributes
a) (CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Dimension) -> CInt -> Dimension
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_height WindowAttributes
a)
newtype FixedLayout a = FixedLayout [Rectangle] deriving (ReadPrec [FixedLayout a]
ReadPrec (FixedLayout a)
Int -> ReadS (FixedLayout a)
ReadS [FixedLayout a]
(Int -> ReadS (FixedLayout a))
-> ReadS [FixedLayout a]
-> ReadPrec (FixedLayout a)
-> ReadPrec [FixedLayout a]
-> Read (FixedLayout a)
forall a. ReadPrec [FixedLayout a]
forall a. ReadPrec (FixedLayout a)
forall a. Int -> ReadS (FixedLayout a)
forall a. ReadS [FixedLayout a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FixedLayout a]
$creadListPrec :: forall a. ReadPrec [FixedLayout a]
readPrec :: ReadPrec (FixedLayout a)
$creadPrec :: forall a. ReadPrec (FixedLayout a)
readList :: ReadS [FixedLayout a]
$creadList :: forall a. ReadS [FixedLayout a]
readsPrec :: Int -> ReadS (FixedLayout a)
$creadsPrec :: forall a. Int -> ReadS (FixedLayout a)
Read,Int -> FixedLayout a -> String -> String
[FixedLayout a] -> String -> String
FixedLayout a -> String
(Int -> FixedLayout a -> String -> String)
-> (FixedLayout a -> String)
-> ([FixedLayout a] -> String -> String)
-> Show (FixedLayout a)
forall a. Int -> FixedLayout a -> String -> String
forall a. [FixedLayout a] -> String -> String
forall a. FixedLayout a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FixedLayout a] -> String -> String
$cshowList :: forall a. [FixedLayout a] -> String -> String
show :: FixedLayout a -> String
$cshow :: forall a. FixedLayout a -> String
showsPrec :: Int -> FixedLayout a -> String -> String
$cshowsPrec :: forall a. Int -> FixedLayout a -> String -> String
Show)
instance LayoutClass FixedLayout a where
doLayout :: FixedLayout a
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (FixedLayout a))
doLayout (FixedLayout [Rectangle]
rs) Rectangle
_ Stack a
s = ([(a, Rectangle)], Maybe (FixedLayout a))
-> X ([(a, Rectangle)], Maybe (FixedLayout a))
forall (m :: * -> *) a. Monad m => a -> m a
return ([a] -> [Rectangle] -> [(a, Rectangle)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Stack a -> [a]
forall a. Stack a -> [a]
W.integrate Stack a
s) [Rectangle]
rs, Maybe (FixedLayout a)
forall a. Maybe a
Nothing)
fixedLayout :: [Rectangle] -> FixedLayout a
fixedLayout :: [Rectangle] -> FixedLayout a
fixedLayout = [Rectangle] -> FixedLayout a
forall a. [Rectangle] -> FixedLayout a
FixedLayout