mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
Updates to work with recent API changes
This commit is contained in:
parent
e8e8457e4c
commit
fca67d33d7
@ -2,9 +2,10 @@ module XMonadContrib.Circle (circle) where -- actually it's an ellipse
|
||||
|
||||
import Graphics.X11.Xlib
|
||||
import XMonad
|
||||
import StackSet (integrate)
|
||||
|
||||
circle :: Layout
|
||||
circle = Layout { doLayout = circleLayout,
|
||||
circle = Layout { doLayout = \r -> circleLayout r . integrate,
|
||||
modifyLayout = return . const Nothing }
|
||||
|
||||
circleLayout :: Rectangle -> [Window] -> X [(Window, Rectangle)]
|
||||
|
@ -25,7 +25,7 @@
|
||||
|
||||
module XMonadContrib.GreedyView (greedyView) where
|
||||
|
||||
import StackSet as W
|
||||
import StackSet as W hiding (filter)
|
||||
import XMonad
|
||||
import Operations
|
||||
import Data.List (find)
|
||||
|
@ -2,6 +2,7 @@ module XMonadContrib.HintedTile (tall, wide) where
|
||||
|
||||
import XMonad
|
||||
import Operations (Resize(..), IncMasterN(..), applySizeHints)
|
||||
import qualified StackSet as W
|
||||
import {-# SOURCE #-} Config (borderWidth)
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Xlib.Extras
|
||||
@ -18,10 +19,11 @@ wide = tile splitVertically divideHorizontally
|
||||
tall = tile splitHorizontally divideVertically
|
||||
|
||||
tile split divide nmaster delta frac =
|
||||
Layout { doLayout = \r w -> do { hints <- sequence (map getHints w)
|
||||
; return $ zip w (tiler frac r `uncurry` splitAt nmaster hints) }
|
||||
, modifyLayout = \m -> fmap resize (fromMessage m) `mplus`
|
||||
fmap incmastern (fromMessage m) }
|
||||
Layout { doLayout = \r w' -> let w = W.integrate w'
|
||||
in do { hints <- sequence (map getHints w)
|
||||
; return $ zip w (tiler frac r `uncurry` splitAt nmaster hints) }
|
||||
, modifyLayout = \m -> return $ fmap resize (fromMessage m) `mplus`
|
||||
fmap incmastern (fromMessage m) }
|
||||
|
||||
where resize Shrink = tile split divide nmaster delta (frac-delta)
|
||||
resize Expand = tile split divide nmaster delta (frac+delta)
|
||||
|
@ -31,6 +31,7 @@ import Data.Ratio
|
||||
import Graphics.X11.Xlib
|
||||
import XMonad hiding ( trace )
|
||||
import Operations ( full, Resize(Shrink, Expand) )
|
||||
import qualified StackSet as W
|
||||
import qualified Data.Map as M
|
||||
import Data.List ( sort )
|
||||
import Data.Typeable ( Typeable )
|
||||
@ -68,7 +69,7 @@ flexibility :: Double
|
||||
flexibility = 0.1
|
||||
|
||||
mosaic :: Double -> Double -> M.Map NamedWindow [WindowHint] -> Layout
|
||||
mosaic delta tileFrac hints = full { doLayout = mosaicL tileFrac hints, modifyLayout = return . mlayout }
|
||||
mosaic delta tileFrac hints = full { doLayout = \r -> mosaicL tileFrac hints r . W.integrate, modifyLayout = return . mlayout }
|
||||
where mlayout x = (m1 `fmap` fromMessage x) `mplus` (m2 `fmap` fromMessage x)
|
||||
m1 Shrink = mosaic delta (tileFrac/(1+delta)) hints
|
||||
m1 Expand = mosaic delta (tileFrac*(1+delta)) hints
|
||||
|
@ -13,7 +13,7 @@ import Data.List ( sortBy )
|
||||
import Data.Maybe ( listToMaybe )
|
||||
|
||||
import XMonad
|
||||
import StackSet
|
||||
import StackSet hiding (filter)
|
||||
import qualified Operations as O
|
||||
|
||||
rotView :: Bool -> X ()
|
||||
|
@ -4,6 +4,7 @@ import Graphics.X11.Xlib
|
||||
import Operations
|
||||
import Data.Ratio
|
||||
import XMonad
|
||||
import qualified StackSet as W
|
||||
|
||||
--
|
||||
-- Spiral layout
|
||||
@ -32,7 +33,7 @@ blend scale ratios = zipWith (+) ratios scaleFactors
|
||||
scaleFactors = map (* step) . reverse . take len $ [0..]
|
||||
|
||||
spiral :: Rational -> Layout
|
||||
spiral scale = Layout { doLayout = fibLayout,
|
||||
spiral scale = Layout { doLayout = \r -> fibLayout r . W.integrate,
|
||||
modifyLayout = \m -> return $ fmap resize $ fromMessage m }
|
||||
where
|
||||
fibLayout sc ws = return $ zip ws rects
|
||||
|
11
Tabbed.hs
11
Tabbed.hs
@ -24,10 +24,11 @@ import XMonadContrib.NamedWindows
|
||||
tabbed :: Layout
|
||||
tabbed = Layout { doLayout = dolay, modifyLayout = const (return Nothing) }
|
||||
|
||||
dolay :: Rectangle -> [Window] -> X [(Window, Rectangle)]
|
||||
dolay sc [w] = return [(w,sc)]
|
||||
dolay sc@(Rectangle x y wid _) ws =
|
||||
do let ts = gentabs x y wid (length ws)
|
||||
dolay :: Rectangle -> W.Stack Window -> X [(Window, Rectangle)]
|
||||
dolay sc (W.Node w [] []) = return [(w,sc)]
|
||||
dolay sc@(Rectangle x y wid _) s@(W.Node w _ _) =
|
||||
do let ws = W.integrate s
|
||||
ts = gentabs x y wid (length ws)
|
||||
tws = zip ts ws
|
||||
maketab (t,w) = newDecoration w t 1 0x000000 0x777777 (drawtab t w) (focus w)
|
||||
drawtab r@(Rectangle _ _ wt ht) w d w' gc =
|
||||
@ -48,7 +49,7 @@ dolay sc@(Rectangle x y wid _) ws =
|
||||
(fromIntegral (wt `div` 2) - fromIntegral (namew `div` 2))
|
||||
(fromIntegral (ht `div` 2) + fromIntegral (nameh `div` 2)) name
|
||||
forM tws maketab
|
||||
return [ (w,shrink sc) | w <- ws ]
|
||||
return [ (w,shrink sc) ]
|
||||
|
||||
shrink :: Rectangle -> Rectangle
|
||||
shrink (Rectangle x y w h) = Rectangle x (y+tabsize) w (h-tabsize)
|
||||
|
@ -13,9 +13,10 @@ import qualified StackSet as W
|
||||
import Control.Monad.State (gets)
|
||||
|
||||
twoPane :: Rational -> Rational -> Layout
|
||||
twoPane delta split = Layout { doLayout = arrange, modifyLayout = message }
|
||||
twoPane delta split = Layout { doLayout = \r -> arrange r . W.integrate, modifyLayout = message }
|
||||
where
|
||||
arrange rect ws@(w:x:_) = do
|
||||
-- TODO this is buggy, it might peek another workspace
|
||||
(Just f) <- gets (W.peek . windowset) -- safe because of pattern match above
|
||||
let y = if f == w then x else f
|
||||
(left, right) = splitHorizontallyBy split rect
|
||||
|
Loading…
x
Reference in New Issue
Block a user