mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-01 04:31:52 -07:00
Apply hlint hints
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
This commit is contained in:
@@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
|
||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Layout.Column
|
||||
@@ -40,7 +40,7 @@ import qualified XMonad.StackSet as W
|
||||
-- In this example, each next window will have height 1.6 times less then
|
||||
-- previous window.
|
||||
|
||||
data Column a = Column Float deriving (Read,Show)
|
||||
newtype Column a = Column Float deriving (Read,Show)
|
||||
|
||||
instance LayoutClass Column a where
|
||||
pureLayout = columnLayout
|
||||
@@ -57,15 +57,13 @@ columnLayout (Column q) rect stack = zip ws rects
|
||||
n = length ws
|
||||
heights = map (xn n rect q) [1..n]
|
||||
ys = [fromIntegral $ sum $ take k heights | k <- [0..n-1]]
|
||||
rects = map (mkRect rect) $ zip heights ys
|
||||
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)
|
||||
h `div` fromIntegral n
|
||||
else
|
||||
round ((fromIntegral h)*q^(n-k)*(1-q)/(1-q^n))
|
||||
|
||||
|
||||
round (fromIntegral h*q^(n-k)*(1-q)/(1-q^n))
|
||||
|
Reference in New Issue
Block a user