Tony Zorman 3d65a6bf72 Refer to the tutorial instead of X.D.Extending more often
Essentially, whenever the tutorial actually has decent material on the
subject matter.  The replacement is roughly done as follows:

  - logHook → tutorial
  - keybindings → tutorial, as this is thoroughly covered
  - manageHook → tutorial + X.D.Extending, as the manageHook stuff the
    tutorial talks about is a little bit of an afterthought.
  - X.D.Extending (on its own) → tutorial + X.D.Extending
  - layoutHook → tutorial + X.D.Extending, as the tutorial, while
    talking about layouts, doesn't necessarily have a huge focus there.
  - mouse bindings → leave this alone, as the tutorial does not at all
    talk about them.
2022-10-21 09:17:43 +02:00

76 lines
2.7 KiB
Haskell

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.Circle
-- Description : An elliptical, overlapping layout.
-- Copyright : (c) Peter De Wachter
-- License : BSD-style (see LICENSE)
--
-- Maintainer : Peter De Wachter <pdewacht@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
-- Circle is an elliptical, overlapping layout, by Peter De Wachter
--
-----------------------------------------------------------------------------
module XMonad.Layout.Circle (
-- * Usage
-- $usage
Circle (..)
) where -- actually it's an ellipse
import XMonad.Prelude
import XMonad
import XMonad.StackSet (integrate, peek)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.Circle
--
-- Then edit your @layoutHook@ by adding the Circle layout:
--
-- > myLayout = Circle ||| Full ||| etc..
-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
data Circle a = Circle deriving ( Read, Show )
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