mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
some renaming of classes and data types.
This commit is contained in:
parent
12c4318b03
commit
db1026f6e9
@ -10,7 +10,7 @@
|
||||
-- Stability : unstable
|
||||
-- Portability : unportable
|
||||
--
|
||||
-- Layout that puts non-focused windows in ribbons at the top and bottom
|
||||
-- LayoutClass that puts non-focused windows in ribbons at the top and bottom
|
||||
-- of the screen.
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
@ -34,7 +34,7 @@ import Data.Ratio
|
||||
|
||||
data Accordion a = Accordion deriving ( Read, Show )
|
||||
|
||||
instance Layout Accordion Window where
|
||||
instance LayoutClass Accordion Window where
|
||||
pureLayout _ sc ws = zip ups tops ++ [(W.focus ws, mainPane)] ++ zip dns bottoms
|
||||
where
|
||||
ups = W.up ws
|
||||
|
@ -33,7 +33,7 @@ import StackSet (integrate, peek)
|
||||
|
||||
data Circle a = Circle deriving ( Read, Show )
|
||||
|
||||
instance Layout Circle Window where
|
||||
instance LayoutClass Circle Window where
|
||||
doLayout Circle r s = do layout <- raiseFocus $ circleLayout r $ integrate s
|
||||
return (layout, Nothing)
|
||||
|
||||
|
12
Combo.hs
12
Combo.hs
@ -50,15 +50,15 @@ import qualified StackSet as W ( differentiate )
|
||||
-- %import XMonadContrib.Combo
|
||||
-- %layout , combo (twoPane 0.03 0.5) [(full,1),(tabbed shrinkText defaultTConf,1)]
|
||||
|
||||
combo :: (Eq a, Show a, Read a, ReadableSomeLayout a, Layout l (SomeLayout a, Int))
|
||||
=> (l (SomeLayout a, Int)) -> [(SomeLayout a, Int)] -> Combo l a
|
||||
combo :: (Eq a, Show a, Read a, ReadableLayout a, LayoutClass l (Layout a, Int))
|
||||
=> (l (Layout a, Int)) -> [(Layout a, Int)] -> Combo l a
|
||||
combo = Combo []
|
||||
|
||||
data Combo l a = Combo [a] (l (SomeLayout a, Int)) [(SomeLayout a, Int)]
|
||||
data Combo l a = Combo [a] (l (Layout a, Int)) [(Layout a, Int)]
|
||||
deriving ( Show, Read )
|
||||
|
||||
instance (Eq a, Show a, Read a, ReadableSomeLayout a, Layout l (SomeLayout a, Int))
|
||||
=> Layout (Combo l) a where
|
||||
instance (Eq a, Show a, Read a, ReadableLayout a, LayoutClass l (Layout a, Int))
|
||||
=> LayoutClass (Combo l) a where
|
||||
doLayout (Combo f super origls) rinput s = arrange (integrate s)
|
||||
where arrange [] = return ([], Just $ Combo [] super origls)
|
||||
arrange [w] = return ([(w,rinput)], Just $ Combo [w] super origls)
|
||||
@ -89,7 +89,7 @@ instance (Eq a, Show a, Read a, ReadableSomeLayout a, Layout l (SomeLayout a, In
|
||||
Just [super'] -> return $ Just $ Combo f super' $ maybe origls id mls'
|
||||
_ -> return $ Combo f super `fmap` mls'
|
||||
|
||||
broadcastPrivate :: Layout l b => SomeMessage -> [l b] -> X (Maybe [l b])
|
||||
broadcastPrivate :: LayoutClass l b => SomeMessage -> [l b] -> X (Maybe [l b])
|
||||
broadcastPrivate a ol = do nml <- mapM f ol
|
||||
if any isJust nml
|
||||
then return $ Just $ zipWith ((flip maybe) id) ol nml
|
||||
|
@ -63,7 +63,7 @@ data DragPane a =
|
||||
|
||||
data DragType = Horizontal | Vertical deriving ( Show, Read )
|
||||
|
||||
instance Layout DragPane Window where
|
||||
instance LayoutClass DragPane Window where
|
||||
doLayout d@(DragPane _ Vertical _ _) = doLay id d
|
||||
doLayout d@(DragPane _ Horizontal _ _) = doLay mirrorRect d
|
||||
handleMessage = handleMess
|
||||
|
@ -21,7 +21,7 @@ module XMonadContrib.DynamicWorkspaces (
|
||||
|
||||
import Control.Monad.State ( gets )
|
||||
|
||||
import XMonad ( X, XState(..), SomeLayout, WorkspaceId )
|
||||
import XMonad ( X, XState(..), Layout, WorkspaceId )
|
||||
import Operations
|
||||
import StackSet hiding (filter, modify, delete)
|
||||
import Graphics.X11.Xlib ( Window )
|
||||
@ -37,7 +37,7 @@ import Graphics.X11.Xlib ( Window )
|
||||
allPossibleTags :: [WorkspaceId]
|
||||
allPossibleTags = map (:"") ['0'..]
|
||||
|
||||
addWorkspace :: SomeLayout Window -> X ()
|
||||
addWorkspace :: Layout Window -> X ()
|
||||
addWorkspace l = do s <- gets windowset
|
||||
let newtag:_ = filter (not . (`tagMember` s)) allPossibleTags
|
||||
windows (addWorkspace' newtag l)
|
||||
|
@ -34,7 +34,7 @@ import XMonadContrib.LayoutModifier
|
||||
-- %layout , layoutHints $ tiled
|
||||
-- %layout , layoutHints $ mirror tiled
|
||||
|
||||
layoutHints :: (Layout l a) => l a -> ModifiedLayout LayoutHints l a
|
||||
layoutHints :: (LayoutClass l a) => l a -> ModifiedLayout LayoutHints l a
|
||||
layoutHints = ModifiedLayout LayoutHints
|
||||
|
||||
-- | Expand a size by the given multiple of the border width. The
|
||||
|
@ -28,8 +28,8 @@ import Operations ( LayoutMessages(Hide, ReleaseResources) )
|
||||
-- Use LayoutHelpers to help write easy Layouts.
|
||||
|
||||
class (Show (m a), Read (m a)) => LayoutModifier m a where
|
||||
modifyModify :: m a -> SomeMessage -> X (Maybe (m a))
|
||||
modifyModify m mess | Just Hide <- fromMessage mess = doUnhook
|
||||
handleMess :: m a -> SomeMessage -> X (Maybe (m a))
|
||||
handleMess m mess | Just Hide <- fromMessage mess = doUnhook
|
||||
| Just ReleaseResources <- fromMessage mess = doUnhook
|
||||
| otherwise = return Nothing
|
||||
where doUnhook = do unhook m; return Nothing
|
||||
@ -43,7 +43,7 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
|
||||
modifierDescription :: m a -> String
|
||||
modifierDescription = show
|
||||
|
||||
instance (LayoutModifier m a, Layout l a) => Layout (ModifiedLayout m l) a where
|
||||
instance (LayoutModifier m a, LayoutClass l a) => LayoutClass (ModifiedLayout m l) a where
|
||||
doLayout (ModifiedLayout m l) r s =
|
||||
do (ws, ml') <- doLayout l r s
|
||||
(ws', mm') <- redoLayout m r s ws
|
||||
@ -53,7 +53,7 @@ instance (LayoutModifier m a, Layout l a) => Layout (ModifiedLayout m l) a where
|
||||
return (ws', ml'')
|
||||
handleMessage (ModifiedLayout m l) mess =
|
||||
do ml' <- handleMessage l mess
|
||||
mm' <- modifyModify m mess
|
||||
mm' <- handleMess m mess
|
||||
return $ case mm' of
|
||||
Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
|
||||
Nothing -> (ModifiedLayout m) `fmap` ml'
|
||||
|
@ -56,7 +56,7 @@ import Graphics.X11.Xlib.Extras
|
||||
-- %keybind , ((modMask .|. shiftMask, xK_space), layoutScreens 2 (twoPane 0.5 0.5))
|
||||
-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_space), rescreen)
|
||||
|
||||
layoutScreens :: Layout l Int => Int -> l Int -> X ()
|
||||
layoutScreens :: LayoutClass l Int => Int -> l Int -> X ()
|
||||
layoutScreens nscr _ | nscr < 1 = trace $ "Can't layoutScreens with only " ++ show nscr ++ " screens."
|
||||
layoutScreens nscr l =
|
||||
do rtrect <- asks theRoot >>= getWindowRectangle
|
||||
@ -77,7 +77,7 @@ getWindowRectangle w = withDisplay $ \d ->
|
||||
|
||||
data FixedLayout a = FixedLayout [Rectangle] deriving (Read,Show)
|
||||
|
||||
instance Layout FixedLayout a where
|
||||
instance LayoutClass FixedLayout a where
|
||||
doLayout (FixedLayout rs) _ s = return (zip (W.integrate s) rs, Nothing)
|
||||
|
||||
fixedLayout :: [Rectangle] -> FixedLayout a
|
||||
|
@ -34,10 +34,10 @@ import StackSet
|
||||
|
||||
data MagicFocus l a = MagicFocus (l a) deriving ( Show , Read )
|
||||
|
||||
instance (Layout l Window) => Layout (MagicFocus l) Window where
|
||||
instance (LayoutClass l Window) => LayoutClass (MagicFocus l) Window where
|
||||
doLayout = magicFocus
|
||||
|
||||
magicFocus :: Layout l Window => MagicFocus l Window -> Rectangle
|
||||
magicFocus :: LayoutClass l Window => MagicFocus l Window -> Rectangle
|
||||
-> Stack Window -> X ([(Window, Rectangle)], Maybe (MagicFocus l Window))
|
||||
magicFocus (MagicFocus l) r s =
|
||||
withWindowSet $ \wset -> do
|
||||
|
@ -63,10 +63,10 @@ instance LayoutModifier WithBorder Window where
|
||||
where
|
||||
ws = map fst wrs
|
||||
|
||||
noBorders :: Layout l Window => l Window -> ModifiedLayout WithBorder l Window
|
||||
noBorders :: LayoutClass l Window => l Window -> ModifiedLayout WithBorder l Window
|
||||
noBorders = ModifiedLayout $ WithBorder 0 []
|
||||
|
||||
withBorder :: Layout l a => Dimension -> l a -> ModifiedLayout WithBorder l a
|
||||
withBorder :: LayoutClass l a => Dimension -> l a -> ModifiedLayout WithBorder l a
|
||||
withBorder b = ModifiedLayout $ WithBorder b []
|
||||
|
||||
setBorders :: Dimension -> [Window] -> X ()
|
||||
|
@ -36,7 +36,7 @@ import Data.Ratio
|
||||
|
||||
data Roledex a = Roledex deriving ( Show, Read )
|
||||
|
||||
instance Layout Roledex Window where
|
||||
instance LayoutClass Roledex Window where
|
||||
doLayout _ = roledexLayout
|
||||
|
||||
roledexLayout :: Eq a => Rectangle -> W.Stack a -> X ([(a, Rectangle)], Maybe (Roledex a))
|
||||
|
@ -55,11 +55,11 @@ blend scale ratios = zipWith (+) ratios scaleFactors
|
||||
step = (scale - (1 % 1)) / (fromIntegral len)
|
||||
scaleFactors = map (* step) . reverse . take len $ [0..]
|
||||
|
||||
spiral :: Rational -> Layout a
|
||||
spiral :: Rational -> LayoutClass a
|
||||
spiral = spiralWithDir East CW
|
||||
|
||||
spiralWithDir :: Direction -> Rotation -> Rational -> Layout a
|
||||
spiralWithDir dir rot scale = Layout { doLayout = l2lModDo fibLayout,
|
||||
spiralWithDir :: Direction -> Rotation -> Rational -> LayoutClass a
|
||||
spiralWithDir dir rot scale = LayoutClass { doLayout = l2lModDo fibLayout,
|
||||
modifyLayout = \m -> return $ fmap resize $ fromMessage m }
|
||||
where
|
||||
fibLayout sc ws = zip ws rects
|
||||
|
@ -42,7 +42,7 @@ import StackSet ( integrate )
|
||||
|
||||
data Square a = Square deriving ( Read, Show )
|
||||
|
||||
instance Layout Square a where
|
||||
instance LayoutClass Square a where
|
||||
pureLayout Square r s = arrange (integrate s)
|
||||
where arrange ws@(_:_) = map (\w->(w,rest)) (init ws) ++ [(last ws,sq)]
|
||||
arrange [] = [] -- actually, this is an impossible case
|
||||
|
@ -99,7 +99,7 @@ data Tabbed a =
|
||||
Tabbed (Invisible Maybe TabState) (Invisible Maybe Shrinker) TConf
|
||||
deriving (Show, Read)
|
||||
|
||||
instance Layout Tabbed Window where
|
||||
instance LayoutClass Tabbed Window where
|
||||
doLayout (Tabbed ist ishr conf) = doLay ist ishr conf
|
||||
handleMessage = handleMess
|
||||
description _ = "Tabbed"
|
||||
|
@ -46,7 +46,7 @@ import Graphics.X11.Xlib
|
||||
|
||||
data ThreeCol a = ThreeCol Int Rational Rational deriving (Show,Read)
|
||||
|
||||
instance Layout ThreeCol a where
|
||||
instance LayoutClass ThreeCol a where
|
||||
doLayout (ThreeCol nmaster _ frac) r =
|
||||
return . (\x->(x,Nothing)) .
|
||||
ap zip (tile3 frac r nmaster . length) . W.integrate
|
||||
|
@ -43,7 +43,7 @@ data TwoPane a =
|
||||
TwoPane Rational Rational
|
||||
deriving ( Show, Read )
|
||||
|
||||
instance Layout TwoPane a where
|
||||
instance LayoutClass TwoPane a where
|
||||
doLayout (TwoPane _ split) r s = return (arrange r s,Nothing)
|
||||
where
|
||||
arrange rect st = case reverse (up st) of
|
||||
|
@ -93,7 +93,7 @@ instance LayoutModifier WindowNavigation Window where
|
||||
--mapM_ (\(w,c) -> sc c w) wnavigablec
|
||||
return (wrs, Just $ WindowNavigation $ I $ Just $ NS pt wnavigable)
|
||||
|
||||
modifyModify (WindowNavigation (I (Just (NS pt wrs)))) m
|
||||
handleMess (WindowNavigation (I (Just (NS pt wrs)))) m
|
||||
| Just (Go d) <- fromMessage m =
|
||||
case sortby d $ filter (inr d pt . snd) wrs of
|
||||
[] -> return Nothing
|
||||
@ -105,8 +105,8 @@ instance LayoutModifier WindowNavigation Window where
|
||||
mapM_ (sc (Just nbc) . fst) wrs
|
||||
return $ Just $ WindowNavigation $ I $ Just $ NS pt []
|
||||
| Just ReleaseResources <- fromMessage m =
|
||||
modifyModify (WindowNavigation (I $ Just (NS pt wrs))) (SomeMessage Hide)
|
||||
modifyModify _ _ = return Nothing
|
||||
handleMess (WindowNavigation (I $ Just (NS pt wrs))) (SomeMessage Hide)
|
||||
handleMess _ _ = return Nothing
|
||||
|
||||
truncHead (x:_) = [x]
|
||||
truncHead [] = []
|
||||
|
@ -60,10 +60,10 @@ data WorkspaceDir a = WorkspaceDir String deriving ( Read, Show )
|
||||
|
||||
instance LayoutModifier WorkspaceDir a where
|
||||
hook (WorkspaceDir s) = scd s
|
||||
modifyModify (WorkspaceDir _) m = return $ do Chdir wd <- fromMessage m
|
||||
handleMess (WorkspaceDir _) m = return $ do Chdir wd <- fromMessage m
|
||||
Just (WorkspaceDir wd)
|
||||
|
||||
workspaceDir :: Layout l a => String -> l a
|
||||
workspaceDir :: LayoutClass l a => String -> l a
|
||||
-> ModifiedLayout WorkspaceDir l a
|
||||
workspaceDir s = ModifiedLayout (WorkspaceDir s)
|
||||
|
||||
|
Loading…
x
Reference in New Issue
Block a user