Skip to content

Commit 29f200d

Browse files
committed
True PerScreen implementation
The old PerScreen module has been renamed to X.L.IfWidth, and is re-exported for backward compatibility with a deprecation notice. The new PerScreen supports specifying screens by ScreenId (literal numbers will work because it has a Num instance).
1 parent 7bb1f0b commit 29f200d

File tree

4 files changed

+174
-40
lines changed

4 files changed

+174
-40
lines changed

CHANGES.md

+9
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,15 @@
8181

8282
### New Modules
8383

84+
* `XMonad.Layout.IfWidth`
85+
- The `ifWidth` layout modifier from `XMonad.Layout.PerScreen` has been moved
86+
here. It is re-exported by the new `PerScreen` module, but is marked as
87+
deprecated with a pointer to this module.
88+
89+
* `XMonad.Layout.PerScreen`
90+
- A complete reimplementation that provides proper `onScreen` and `onScreens`
91+
layout modifiers. It also re-exports `ifWidth` for backward compatibility.
92+
8493
* `XMonad.Layout.CenterMainFluid`
8594
- A three column layout with main column in the center and two stack
8695
column surrounding it. Master window will be on center column and

XMonad/Layout/IfWidth.hs

+77
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,77 @@
1+
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
2+
3+
-----------------------------------------------------------------------------
4+
-- |
5+
-- Module : XMonad.Layout.IfWidth
6+
-- Description : Configure layouts based on the width of your screen.
7+
-- Copyright : (c) Edward Z. Yang
8+
-- License : BSD-style (see LICENSE)
9+
--
10+
-- Maintainer : <[email protected]>
11+
-- Stability : unstable
12+
-- Portability : unportable
13+
--
14+
-- Configure layouts based on the width of your screen; use your
15+
-- favorite multi-column layout for wide screens and a full-screen
16+
-- layout for small ones.
17+
-----------------------------------------------------------------------------
18+
19+
module XMonad.Layout.IfWidth
20+
( -- * Usage
21+
-- $usage
22+
PerScreen,
23+
ifWider
24+
) where
25+
26+
import XMonad
27+
import qualified XMonad.StackSet as W
28+
29+
import XMonad.Prelude (fromMaybe)
30+
31+
-- $usage
32+
-- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
33+
--
34+
-- > import XMonad.Layout.ByWidth
35+
--
36+
-- and modifying your layoutHook as follows (for example):
37+
--
38+
-- > layoutHook = ifWider 1280 (Tall 1 (3/100) (1/2) ||| Full) Full
39+
--
40+
-- Replace any of the layouts with any arbitrarily complicated layout.
41+
-- 'ifWider' can also be used inside other layout combinators.
42+
--
43+
-- For backward compatibility, the type constructor is still called 'PerScreen'.
44+
45+
ifWider :: (LayoutClass l1 a, LayoutClass l2 a)
46+
=> Dimension -- ^ target screen width
47+
-> l1 a -- ^ layout to use when the screen is wide enough
48+
-> l2 a -- ^ layout to use otherwise
49+
-> PerScreen l1 l2 a
50+
ifWider w = PerScreen w False
51+
52+
data PerScreen l1 l2 a = PerScreen Dimension Bool (l1 a) (l2 a) deriving (Read, Show)
53+
54+
-- | Construct new PerScreen values with possibly modified layouts.
55+
mkNewPerScreenT :: PerScreen l1 l2 a -> Maybe (l1 a) ->
56+
PerScreen l1 l2 a
57+
mkNewPerScreenT (PerScreen w _ lt lf) mlt' =
58+
(\lt' -> PerScreen w True lt' lf) $ fromMaybe lt mlt'
59+
60+
mkNewPerScreenF :: PerScreen l1 l2 a -> Maybe (l2 a) ->
61+
PerScreen l1 l2 a
62+
mkNewPerScreenF (PerScreen w _ lt lf) mlf' =
63+
PerScreen w False lt $ fromMaybe lf mlf'
64+
65+
instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (PerScreen l1 l2) a where
66+
runLayout (W.Workspace i p@(PerScreen w _ lt lf) ms) r
67+
| rect_width r > w = do (wrs, mlt') <- runLayout (W.Workspace i lt ms) r
68+
return (wrs, Just $ mkNewPerScreenT p mlt')
69+
| otherwise = do (wrs, mlt') <- runLayout (W.Workspace i lf ms) r
70+
return (wrs, Just $ mkNewPerScreenF p mlt')
71+
72+
handleMessage (PerScreen w bool lt lf) m
73+
| bool = handleMessage lt m >>= maybe (return Nothing) (\nt -> return . Just $ PerScreen w bool nt lf)
74+
| otherwise = handleMessage lf m >>= maybe (return Nothing) (return . Just . PerScreen w bool lt)
75+
76+
description (PerScreen _ True l1 _) = description l1
77+
description (PerScreen _ _ _ l2) = description l2

XMonad/Layout/PerScreen.hs

+87-40
Original file line numberDiff line numberDiff line change
@@ -3,73 +3,120 @@
33
-----------------------------------------------------------------------------
44
-- |
55
-- Module : XMonad.Layout.PerScreen
6-
-- Description : Configure layouts based on the width of your screen.
7-
-- Copyright : (c) Edward Z. Yang
6+
-- Description : Configure layouts based on the screen rectangle.
7+
-- Copyright : (c) Brandon S. Allbery KF8NH
88
-- License : BSD-style (see LICENSE)
99
--
10-
-- Maintainer : <[email protected]>
10+
-- Maintainer : <[email protected]>
1111
-- Stability : unstable
1212
-- Portability : unportable
1313
--
14-
-- Configure layouts based on the width of your screen; use your
15-
-- favorite multi-column layout for wide screens and a full-screen
16-
-- layout for small ones.
14+
-- Configure layouts based on the screen rectangle passed to the layout.
15+
-- This gives you true per-screen functionality.
16+
--
17+
-- The old PerScreen is now X.L.ByWidth. We re-export it deprecated for
18+
-- backward compatibility.
1719
-----------------------------------------------------------------------------
1820

1921
module XMonad.Layout.PerScreen
2022
( -- * Usage
2123
-- $usage
22-
PerScreen,
24+
OnScreen,
25+
onScreen,
26+
onScreens,
27+
-- * Deprecated
28+
-- $deprecated
29+
IW.PerScreen,
2330
ifWider
2431
) where
2532

2633
import XMonad
2734
import qualified XMonad.StackSet as W
2835

29-
import XMonad.Prelude (fromMaybe)
36+
import XMonad.Prelude (fromMaybe, fi)
37+
38+
import qualified XMonad.Layout.IfWidth as IW
39+
40+
import Data.List (find)
3041

3142
-- $usage
3243
-- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
3344
--
34-
-- > import XMonad.Layout.PerScreen
45+
-- > import XMonad.Layout.OnScreen
3546
--
3647
-- and modifying your layoutHook as follows (for example):
3748
--
38-
-- > layoutHook = ifWider 1280 (Tall 1 (3/100) (1/2) ||| Full) Full
49+
-- > layoutHook = onScreen 1 (Tall 1 (3/100) (1/2) ||| Full) Full
3950
--
4051
-- Replace any of the layouts with any arbitrarily complicated layout.
41-
-- ifWider can also be used inside other layout combinators.
52+
-- 'onScreen' can also be used inside other layout combinators, although the
53+
-- result may be confusing.
54+
55+
-- | Specify a layout to run on a given screen.
56+
onScreen :: (LayoutClass l1 a, LayoutClass l2 a)
57+
=> ScreenId -> l1 a -> l2 a -> OnScreen l1 l2 a
58+
onScreen s = onScreens [s]
59+
60+
-- | Specify a layout to run on a list of screens.
61+
-- Note that this works by 'ScreenId'. It has a 'Num' instance, so literal
62+
-- screen numbers will work as expected, but if you use a binding you need
63+
-- to use the 'S' constructor.
64+
onScreens :: (LayoutClass l1 a, LayoutClass l2 a)
65+
=> [ScreenId] -> l1 a -> l2 a -> OnScreen l1 l2 a
66+
onScreens ss l1 l2 = OnScreen ss l1 l2 False
67+
68+
data OnScreen l1 l2 a = OnScreen [ScreenId] (l1 a) (l2 a) Bool
69+
deriving (Read, Show)
70+
71+
instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (OnScreen l1 l2) a where
72+
runLayout (W.Workspace i p@(OnScreen ss l1 l2 _) ms) r = do
73+
which <- withWindowSet $ \ws -> do
74+
let srs = sinfo (W.current ws) : map sinfo (W.visible ws)
75+
f lr (_,sr) = rect_x lr >= rect_x sr &&
76+
rect_x lr < rect_x sr + fi (rect_width sr) &&
77+
rect_y lr >= rect_y sr &&
78+
rect_y lr < rect_y sr + fi (rect_height sr)
79+
sinfo (W.Screen _ sid (SD sd)) = (sid, sd)
80+
return $ maybe 0 fst (find (f r) srs) `elem` ss
81+
if which
82+
then do handleMessage l2 (SomeMessage Hide)
83+
(wrs, mlt') <- runLayout (W.Workspace i l1 ms) r
84+
return (wrs, Just $ updateL1 p mlt')
85+
else do handleMessage l1 (SomeMessage Hide)
86+
(wrs, mlt') <- runLayout (W.Workspace i l2 ms) r
87+
return (wrs, Just $ updateL2 p mlt')
88+
89+
handleMessage (OnScreen ss l1 l2 b) m
90+
| fromMessage m == Just Hide = do
91+
l1' <- handleMessage l1 m
92+
l2' <- handleMessage l2 m
93+
return $ Just $ OnScreen ss (fromMaybe l1 l1') (fromMaybe l2 l2') b
94+
| fromMessage m == Just ReleaseResources = do
95+
l1' <- handleMessage l1 m
96+
l2' <- handleMessage l2 m
97+
return $ Just $ OnScreen ss (fromMaybe l1 l1') (fromMaybe l2 l2') b
98+
| b = handleMessage l1 m >>= maybe (return Nothing) (\nl1 -> return . Just $ OnScreen ss nl1 l2 b)
99+
| otherwise = handleMessage l2 m >>= maybe (return Nothing) (\nl2 -> return . Just $ OnScreen ss l1 nl2 b)
100+
101+
description (OnScreen _ l1 _ True ) = description l1
102+
description (OnScreen _ _ l2 False) = description l2
103+
104+
updateL1 :: OnScreen l1 l2 a -> Maybe (l1 a) -> OnScreen l1 l2 a
105+
updateL1 (OnScreen ss l1 l2 _) mlt = OnScreen ss (fromMaybe l1 mlt) l2 True
106+
107+
updateL2 :: OnScreen l1 l2 a -> Maybe (l2 a) -> OnScreen l1 l2 a
108+
updateL2 (OnScreen ss l1 l2 _) mlt = OnScreen ss l1 (fromMaybe l2 mlt) False
109+
110+
-- $deprecated
111+
-- Older versions of this module exported an 'ifWidth' layout modifier. This
112+
-- has been moved to 'XMonad.Layout.IfWidth', but is re-exported for backward
113+
-- compatibility. It is deprecated and will be removed in favor of 'IfWidth'
114+
-- in a future release.
42115

43116
ifWider :: (LayoutClass l1 a, LayoutClass l2 a)
44117
=> Dimension -- ^ target screen width
45118
-> l1 a -- ^ layout to use when the screen is wide enough
46119
-> l2 a -- ^ layout to use otherwise
47-
-> PerScreen l1 l2 a
48-
ifWider w = PerScreen w False
49-
50-
data PerScreen l1 l2 a = PerScreen Dimension Bool (l1 a) (l2 a) deriving (Read, Show)
51-
52-
-- | Construct new PerScreen values with possibly modified layouts.
53-
mkNewPerScreenT :: PerScreen l1 l2 a -> Maybe (l1 a) ->
54-
PerScreen l1 l2 a
55-
mkNewPerScreenT (PerScreen w _ lt lf) mlt' =
56-
(\lt' -> PerScreen w True lt' lf) $ fromMaybe lt mlt'
57-
58-
mkNewPerScreenF :: PerScreen l1 l2 a -> Maybe (l2 a) ->
59-
PerScreen l1 l2 a
60-
mkNewPerScreenF (PerScreen w _ lt lf) mlf' =
61-
PerScreen w False lt $ fromMaybe lf mlf'
62-
63-
instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (PerScreen l1 l2) a where
64-
runLayout (W.Workspace i p@(PerScreen w _ lt lf) ms) r
65-
| rect_width r > w = do (wrs, mlt') <- runLayout (W.Workspace i lt ms) r
66-
return (wrs, Just $ mkNewPerScreenT p mlt')
67-
| otherwise = do (wrs, mlt') <- runLayout (W.Workspace i lf ms) r
68-
return (wrs, Just $ mkNewPerScreenF p mlt')
69-
70-
handleMessage (PerScreen w bool lt lf) m
71-
| bool = handleMessage lt m >>= maybe (return Nothing) (\nt -> return . Just $ PerScreen w bool nt lf)
72-
| otherwise = handleMessage lf m >>= maybe (return Nothing) (return . Just . PerScreen w bool lt)
73-
74-
description (PerScreen _ True l1 _) = description l1
75-
description (PerScreen _ _ _ l2) = description l2
120+
-> IW.PerScreen l1 l2 a
121+
ifWider = IW.ifWider
122+
{-# DEPRECATED ifWider "Use XMonad.Layout.IfWidth.ifWider instead" #-}

xmonad-contrib.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -261,6 +261,7 @@ library
261261
XMonad.Layout.HintedTile
262262
XMonad.Layout.IM
263263
XMonad.Layout.IfMax
264+
XMonad.Layout.IfWidth
264265
XMonad.Layout.ImageButtonDecoration
265266
XMonad.Layout.IndependentScreens
266267
XMonad.Layout.LayoutBuilder

0 commit comments

Comments
 (0)