mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-03 13:41:53 -07:00
.github
XMonad
Actions
Config
Doc
Hooks
Layout
Groups
MultiToggle
Accordion.hs
AutoMaster.hs
AvoidFloats.hs
BinaryColumn.hs
BinarySpacePartition.hs
BorderResize.hs
BoringWindows.hs
ButtonDecoration.hs
CenteredMaster.hs
Circle.hs
Column.hs
Combo.hs
ComboP.hs
Cross.hs
Decoration.hs
DecorationAddons.hs
DecorationMadness.hs
Dishes.hs
DragPane.hs
DraggingVisualizer.hs
Drawer.hs
Dwindle.hs
DwmStyle.hs
FixedAspectRatio.hs
FixedColumn.hs
Fullscreen.hs
Gaps.hs
Grid.hs
GridVariants.hs
Groups.hs
Hidden.hs
HintedGrid.hs
HintedTile.hs
IM.hs
IfMax.hs
ImageButtonDecoration.hs
IndependentScreens.hs
LayoutBuilder.hs
LayoutBuilderP.hs
LayoutCombinators.hs
LayoutHints.hs
LayoutModifier.hs
LayoutScreens.hs
LimitWindows.hs
MagicFocus.hs
Magnifier.hs
Master.hs
Maximize.hs
MessageControl.hs
Minimize.hs
Monitor.hs
Mosaic.hs
MosaicAlt.hs
MouseResizableTile.hs
MultiColumns.hs
MultiDishes.hs
MultiToggle.hs
Named.hs
NoBorders.hs
NoFrillsDecoration.hs
OnHost.hs
OneBig.hs
PerScreen.hs
PerWorkspace.hs
PositionStoreFloat.hs
Reflect.hs
Renamed.hs
ResizableThreeColumns.hs
ResizableTile.hs
ResizeScreen.hs
Roledex.hs
ShowWName.hs
SimpleDecoration.hs
SimpleFloat.hs
Simplest.hs
SimplestFloat.hs
SortedLayout.hs
Spacing.hs
Spiral.hs
Square.hs
StackTile.hs
StateFull.hs
Stoppable.hs
SubLayouts.hs
TabBarDecoration.hs
Tabbed.hs
TallMastersCombo.hs
ThreeColumns.hs
ToggleLayouts.hs
TrackFloating.hs
TwoPane.hs
TwoPanePersistent.hs
VoidBorders.hs
WindowArranger.hs
WindowNavigation.hs
WindowSwitcherDecoration.hs
WorkspaceDir.hs
ZoomRow.hs
Prompt
Util
Doc.hs
Prelude.hs
Prompt.hs
scripts
tests
.gitignore
.hlint.yaml
.mailmap
CHANGES.md
LICENSE
README.md
Setup.lhs
cabal.haskell-ci
cabal.project
flake.nix
stack-master.yaml
stack.yaml
xmonad-contrib.cabal
All hints are applied in one single commit, as a commit per hint would result in 80+ separate commits—tihs is really just too much noise. Related: https://github.com/xmonad/xmonad-contrib/issues/537
70 lines
2.6 KiB
Haskell
70 lines
2.6 KiB
Haskell
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
|
|
-----------------------------------------------------------------------------
|
|
-- |
|
|
-- Module : XMonad.Layout.Column
|
|
-- Copyright : (c) 2009 Ilya Portnov
|
|
-- License : BSD3-style (see LICENSE)
|
|
--
|
|
-- Maintainer : Ilya Portnov <portnov84@rambler.ru>
|
|
-- Stability : unstable
|
|
-- Portability : unportable
|
|
--
|
|
-- Provides Column layout that places all windows in one column. Windows
|
|
-- heights are calculated from equation: H1/H2 = H2/H3 = ... = q, where q is
|
|
-- given. With Shrink/Expand messages you can change the q value.
|
|
--
|
|
-----------------------------------------------------------------------------
|
|
|
|
module XMonad.Layout.Column (
|
|
-- * Usage
|
|
-- $usage
|
|
Column (..)
|
|
) where
|
|
import XMonad
|
|
import qualified XMonad.StackSet as W
|
|
|
|
-- $usage
|
|
-- This module defines layot named Column. It places all windows in one
|
|
-- column. Windows heights are calculated from equation: H1/H2 = H2/H3 = ... =
|
|
-- q, where `q' is given (thus, windows heights are members of geometric
|
|
-- progression). With Shrink/Expand messages one can change the `q' value.
|
|
--
|
|
-- You can use this module by adding folowing in your @xmonad.hs@:
|
|
--
|
|
-- > import XMonad.Layout.Column
|
|
--
|
|
-- Then add layouts to your layoutHook:
|
|
--
|
|
-- > myLayoutHook = Column 1.6 ||| ...
|
|
--
|
|
-- In this example, each next window will have height 1.6 times less then
|
|
-- previous window.
|
|
|
|
newtype Column a = Column Float deriving (Read,Show)
|
|
|
|
instance LayoutClass Column a where
|
|
pureLayout = columnLayout
|
|
pureMessage = columnMessage
|
|
|
|
columnMessage :: Column a -> SomeMessage -> Maybe (Column a)
|
|
columnMessage (Column q) m = fmap resize (fromMessage m)
|
|
where resize Shrink = Column (q-0.1)
|
|
resize Expand = Column (q+0.1)
|
|
|
|
columnLayout :: Column a -> Rectangle -> W.Stack a -> [(a,Rectangle)]
|
|
columnLayout (Column q) rect stack = zip ws rects
|
|
where ws = W.integrate stack
|
|
n = length ws
|
|
heights = map (xn n rect q) [1..n]
|
|
ys = [fromIntegral $ sum $ take k heights | k <- [0..n-1]]
|
|
rects = zipWith (curry (mkRect rect)) heights ys
|
|
|
|
mkRect :: Rectangle -> (Dimension,Position) -> Rectangle
|
|
mkRect (Rectangle xs ys ws _) (h,y) = Rectangle xs (ys+fromIntegral y) ws h
|
|
|
|
xn :: Int -> Rectangle -> Float -> Int -> Dimension
|
|
xn n (Rectangle _ _ _ h) q k = if q==1 then
|
|
h `div` fromIntegral n
|
|
else
|
|
round (fromIntegral h*q^(n-k)*(1-q)/(1-q^n))
|