X.L.Circle: Deprecate in favour of X.L.CircleEx

This commit is contained in:
Ilya V. Portnov 2023-12-17 13:58:02 +05:00 committed by Tony Zorman
parent 19edf5a7a8
commit 4f2a5c7f43
5 changed files with 52 additions and 80 deletions

View File

@ -76,6 +76,11 @@
- Deprecated the entire module, use `XMonad.Actions.WithAll` - Deprecated the entire module, use `XMonad.Actions.WithAll`
instead. instead.
* `XMonad.Layout.Circle`:
- Deprecated the entire module, use the `circle` function from
`XMonad.Layout.CircleEx` instead.
* `XMonad.Hooks.EwmhDesktops` * `XMonad.Hooks.EwmhDesktops`
- `_NET_CLIENT_LIST_STACKING` puts windows in the current workspace at the - `_NET_CLIENT_LIST_STACKING` puts windows in the current workspace at the

View File

@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -15,15 +16,14 @@
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Layout.Circle ( module XMonad.Layout.Circle {-# DEPRECATED "Use XMonad.Layout.CircleEx instead" #-}
-- * Usage ( -- * Usage
-- $usage -- $usage
Circle (..) pattern Circle
) where -- actually it's an ellipse ) where -- actually it's an ellipse
import XMonad.Prelude import GHC.Real (Ratio(..))
import XMonad import XMonad.Layout.CircleEx
import XMonad.StackSet (integrate, peek)
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@ -39,37 +39,6 @@ import XMonad.StackSet (integrate, peek)
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and -- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
-- "XMonad.Doc.Extending#Editing_the_layout_hook". -- "XMonad.Doc.Extending#Editing_the_layout_hook".
data Circle a = Circle deriving ( Read, Show ) pattern Circle :: CircleEx a
pattern Circle = CircleEx 1 (70 :% 99) (2 :% 5) 1 0
instance LayoutClass Circle Window where
doLayout Circle r s = do layout <- raiseFocus $ circleLayout r $ integrate s
return (layout, Nothing)
circleLayout :: Rectangle -> [a] -> [(a, Rectangle)]
circleLayout _ [] = []
circleLayout r (w:ws) = master : rest
where master = (w, center r)
rest = zip ws $ map (satellite r) [0, pi * 2 / fromIntegral (length ws) ..]
raiseFocus :: [(Window, Rectangle)] -> X [(Window, Rectangle)]
raiseFocus xs = do focused <- withWindowSet (return . peek)
return $ case find ((== focused) . Just . fst) xs of
Just x -> x : delete x xs
Nothing -> xs
center :: Rectangle -> Rectangle
center (Rectangle sx sy sw sh) = Rectangle x y w h
where s = sqrt 2 :: Double
w = round (fromIntegral sw / s)
h = round (fromIntegral sh / s)
x = sx + fromIntegral (sw - w) `div` 2
y = sy + fromIntegral (sh - h) `div` 2
satellite :: Rectangle -> Double -> Rectangle
satellite (Rectangle sx sy sw sh) a = Rectangle (sx + round (rx + rx * cos a))
(sy + round (ry + ry * sin a))
w h
where rx = fromIntegral (sw - w) / 2
ry = fromIntegral (sh - h) / 2
w = sw * 10 `div` 25
h = sh * 10 `div` 25

View File

@ -97,7 +97,7 @@ data CircleEx a = CircleEx
-- * @cMultiplier@ is set to 1, which means all secondary windows -- * @cMultiplier@ is set to 1, which means all secondary windows
-- will have the same size -- will have the same size
-- --
-- This can be used as a drop-in replacement for "XMonad.Layout.Circle.Circle". -- This can be used as a drop-in replacement for "XMonad.Layout.Circle".
circle :: CircleEx a circle :: CircleEx a
circle = CircleEx 1 (70%99) (2%5) 1 0 circle = CircleEx 1 (70%99) (2%5) 1 0

View File

@ -17,7 +17,7 @@ module XMonad.Layout.DecorationMadness
( -- * Usage ( -- * Usage
-- $usage -- $usage
-- * Decorated layouts based on Circle -- * Decorated layouts based on CircleEx
-- $circle -- $circle
circleSimpleDefault circleSimpleDefault
, circleDefault , circleDefault
@ -94,7 +94,7 @@ import XMonad.Layout.SimpleDecoration
import XMonad.Layout.TabBarDecoration import XMonad.Layout.TabBarDecoration
import XMonad.Layout.Accordion import XMonad.Layout.Accordion
import XMonad.Layout.Circle import XMonad.Layout.CircleEx
import XMonad.Layout.WindowArranger import XMonad.Layout.WindowArranger
import XMonad.Layout.SimpleFloat import XMonad.Layout.SimpleFloat
@ -132,39 +132,39 @@ import XMonad.Layout.SimpleFloat
-- "XMonad.Util.Themes" -- "XMonad.Util.Themes"
-- $circle -- $circle
-- Here you will find 'Circle' based decorated layouts. -- Here you will find 'CircleEx' based decorated layouts.
-- | A 'Circle' layout with the xmonad default decoration, default -- | A 'CircleEx' layout with the xmonad default decoration, default
-- theme and default shrinker. -- theme and default shrinker.
-- --
-- Here you can find a screen shot: -- Here you can find a screen shot:
-- --
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefault.png> -- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefault.png>
circleSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Circle Window circleSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) CircleEx Window
circleSimpleDefault = decoration shrinkText def DefaultDecoration Circle circleSimpleDefault = decoration shrinkText def DefaultDecoration circle
-- | Similar to 'circleSimpleDefault' but with the possibility of -- | Similar to 'circleSimpleDefault' but with the possibility of
-- setting a custom shrinker and a custom theme. -- setting a custom shrinker and a custom theme.
circleDefault :: Shrinker s => s -> Theme circleDefault :: Shrinker s => s -> Theme
-> ModifiedLayout (Decoration DefaultDecoration s) Circle Window -> ModifiedLayout (Decoration DefaultDecoration s) CircleEx Window
circleDefault s t = decoration s t DefaultDecoration Circle circleDefault s t = decoration s t DefaultDecoration circle
-- | A 'Circle' layout with the xmonad simple decoration, default -- | A 'CircleEx' layout with the xmonad simple decoration, default
-- theme and default shrinker. -- theme and default shrinker.
-- --
-- Here you can find a screen shot: -- Here you can find a screen shot:
-- --
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDeco.png> -- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDeco.png>
circleSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Circle Window circleSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) CircleEx Window
circleSimpleDeco = decoration shrinkText def (Simple True) Circle circleSimpleDeco = decoration shrinkText def (Simple True) circle
-- | Similar to 'circleSimpleDece' but with the possibility of -- | Similar to 'circleSimpleDece' but with the possibility of
-- setting a custom shrinker and a custom theme. -- setting a custom shrinker and a custom theme.
circleDeco :: Shrinker s => s -> Theme circleDeco :: Shrinker s => s -> Theme
-> ModifiedLayout (Decoration SimpleDecoration s) Circle Window -> ModifiedLayout (Decoration SimpleDecoration s) CircleEx Window
circleDeco s t = decoration s t (Simple True) Circle circleDeco s t = decoration s t (Simple True) circle
-- | A 'Circle' layout with the xmonad default decoration, default -- | A 'CircleEx' layout with the xmonad default decoration, default
-- theme and default shrinker, but with the possibility of moving -- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard. -- windows with the mouse, and resize\/move them with the keyboard.
-- --
@ -172,17 +172,17 @@ circleDeco s t = decoration s t (Simple True) Circle
-- --
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefaultResizable.png> -- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefaultResizable.png>
circleSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) circleSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker)
(ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window (ModifiedLayout MouseResize (ModifiedLayout WindowArranger CircleEx)) Window
circleSimpleDefaultResizable = decoration shrinkText def DefaultDecoration (mouseResize $ windowArrange Circle) circleSimpleDefaultResizable = decoration shrinkText def DefaultDecoration (mouseResize $ windowArrange circle)
-- | Similar to 'circleSimpleDefaultResizable' but with the -- | Similar to 'circleSimpleDefaultResizable' but with the
-- possibility of setting a custom shrinker and a custom theme. -- possibility of setting a custom shrinker and a custom theme.
circleDefaultResizable :: Shrinker s => s -> Theme circleDefaultResizable :: Shrinker s => s -> Theme
-> ModifiedLayout (Decoration DefaultDecoration s) -> ModifiedLayout (Decoration DefaultDecoration s)
(ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window (ModifiedLayout MouseResize (ModifiedLayout WindowArranger CircleEx)) Window
circleDefaultResizable s t = decoration s t DefaultDecoration (mouseResize $ windowArrange Circle) circleDefaultResizable s t = decoration s t DefaultDecoration (mouseResize $ windowArrange circle)
-- | A 'Circle' layout with the xmonad simple decoration, default -- | A 'CircleEx' layout with the xmonad simple decoration, default
-- theme and default shrinker, but with the possibility of moving -- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard. -- windows with the mouse, and resize\/move them with the keyboard.
-- --
@ -190,45 +190,45 @@ circleDefaultResizable s t = decoration s t DefaultDecoration (mouseResize $ win
-- --
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDecoResizable.png> -- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDecoResizable.png>
circleSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) circleSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window (ModifiedLayout MouseResize (ModifiedLayout WindowArranger CircleEx)) Window
circleSimpleDecoResizable = decoration shrinkText def (Simple True) (mouseResize $ windowArrange Circle) circleSimpleDecoResizable = decoration shrinkText def (Simple True) (mouseResize $ windowArrange circle)
-- | Similar to 'circleSimpleDecoResizable' but with the -- | Similar to 'circleSimpleDecoResizable' but with the
-- possibility of setting a custom shrinker and a custom theme. -- possibility of setting a custom shrinker and a custom theme.
circleDecoResizable :: Shrinker s => s -> Theme circleDecoResizable :: Shrinker s => s -> Theme
-> ModifiedLayout (Decoration SimpleDecoration s) -> ModifiedLayout (Decoration SimpleDecoration s)
(ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window (ModifiedLayout MouseResize (ModifiedLayout WindowArranger CircleEx)) Window
circleDecoResizable s t = decoration s t (Simple True) (mouseResize $ windowArrange Circle) circleDecoResizable s t = decoration s t (Simple True) (mouseResize $ windowArrange circle)
-- | A 'Circle' layout with the xmonad DwmStyle decoration, default -- | A 'CircleEx' layout with the xmonad DwmStyle decoration, default
-- theme and default shrinker. -- theme and default shrinker.
-- --
-- Here you can find a screen shot: -- Here you can find a screen shot:
-- --
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDwmStyle.png> -- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDwmStyle.png>
circleSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Circle Window circleSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) CircleEx Window
circleSimpleDwmStyle = decoration shrinkText def Dwm Circle circleSimpleDwmStyle = decoration shrinkText def Dwm circle
-- | Similar to 'circleSimpleDwmStyle' but with the -- | Similar to 'circleSimpleDwmStyle' but with the
-- possibility of setting a custom shrinker and a custom theme. -- possibility of setting a custom shrinker and a custom theme.
circleDwmStyle :: Shrinker s => s -> Theme circleDwmStyle :: Shrinker s => s -> Theme
-> ModifiedLayout (Decoration DwmStyle s) Circle Window -> ModifiedLayout (Decoration DwmStyle s) CircleEx Window
circleDwmStyle s t = decoration s t Dwm Circle circleDwmStyle s t = decoration s t Dwm circle
-- | A 'Circle' layout with the xmonad tabbed decoration, default -- | A 'CircleEx' layout with the xmonad tabbed decoration, default
-- theme and default shrinker. -- theme and default shrinker.
-- --
-- Here you can find a screen shot: -- Here you can find a screen shot:
-- --
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleTabbed.png> -- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleTabbed.png>
circleSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Circle) Window circleSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen CircleEx) Window
circleSimpleTabbed = simpleTabBar Circle circleSimpleTabbed = simpleTabBar circle
-- | Similar to 'circleSimpleTabbed' but with the -- | Similar to 'circleSimpleTabbed' but with the
-- possibility of setting a custom shrinker and a custom theme. -- possibility of setting a custom shrinker and a custom theme.
circleTabbed :: Shrinker s => s -> Theme circleTabbed :: Shrinker s => s -> Theme
-> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Circle) Window -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen CircleEx) Window
circleTabbed s t = tabBar s t Top (resizeVertical (fi $ decoHeight t) Circle) circleTabbed s t = tabBar s t Top (resizeVertical (fi $ decoHeight t) circle)
-- $accordion -- $accordion

View File

@ -47,8 +47,6 @@ module XMonad.Layout.SubLayouts (
) )
where where
import XMonad.Layout.Circle () -- so haddock can find the link
import XMonad.Layout.Decoration(Decoration, DefaultShrinker) import XMonad.Layout.Decoration(Decoration, DefaultShrinker)
import XMonad.Layout.LayoutModifier(LayoutModifier(handleMess, modifyLayout, import XMonad.Layout.LayoutModifier(LayoutModifier(handleMess, modifyLayout,
redoLayout), redoLayout),
@ -184,11 +182,11 @@ import qualified Data.Set as S
-- [@outerLayout@] The layout that determines the rectangles given to each -- [@outerLayout@] The layout that determines the rectangles given to each
-- group. -- group.
-- --
-- Ex. The second group is 'Tall', the third is 'Circle', all others are tabbed -- Ex. The second group is 'Tall', the third is 'XMonad.Layout.CircleEx.circle',
-- with: -- all others are tabbed with:
-- --
-- > myLayout = addTabs shrinkText def -- > myLayout = addTabs shrinkText def
-- > $ subLayout [0,1,2] (Simplest ||| Tall 1 0.2 0.5 ||| Circle) -- > $ subLayout [0,1,2] (Simplest ||| Tall 1 0.2 0.5 ||| circle)
-- > $ Tall 1 0.2 0.5 ||| Full -- > $ Tall 1 0.2 0.5 ||| Full
subLayout :: [Int] -> subl a -> l a -> ModifiedLayout (Sublayout subl) l a subLayout :: [Int] -> subl a -> l a -> ModifiedLayout (Sublayout subl) l a
subLayout nextLayout sl = ModifiedLayout (Sublayout (I []) (nextLayout,sl) []) subLayout nextLayout sl = ModifiedLayout (Sublayout (I []) (nextLayout,sl) [])