mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
Remove trailing whitespace.
This commit is contained in:
parent
3fa51ed656
commit
de84dfef0d
@ -20,7 +20,7 @@
|
|||||||
--
|
--
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
|
|
||||||
module XMonad.Actions.GroupNavigation ( -- * Usage
|
module XMonad.Actions.GroupNavigation ( -- * Usage
|
||||||
-- $usage
|
-- $usage
|
||||||
Direction (..)
|
Direction (..)
|
||||||
, nextMatch
|
, nextMatch
|
||||||
@ -110,13 +110,13 @@ nextMatch dir qry = nextMatchOrDo dir qry (return ())
|
|||||||
-- | Focuses the next window that matches the given boolean query. If
|
-- | Focuses the next window that matches the given boolean query. If
|
||||||
-- there is no such window, perform the given action instead.
|
-- there is no such window, perform the given action instead.
|
||||||
nextMatchOrDo :: Direction -> Query Bool -> X () -> X ()
|
nextMatchOrDo :: Direction -> Query Bool -> X () -> X ()
|
||||||
nextMatchOrDo dir qry act = orderedWindowList dir
|
nextMatchOrDo dir qry act = orderedWindowList dir
|
||||||
>>= focusNextMatchOrDo qry act
|
>>= focusNextMatchOrDo qry act
|
||||||
|
|
||||||
-- Produces the action to perform depending on whether there's a
|
-- Produces the action to perform depending on whether there's a
|
||||||
-- matching window
|
-- matching window
|
||||||
focusNextMatchOrDo :: Query Bool -> X () -> Seq Window -> X ()
|
focusNextMatchOrDo :: Query Bool -> X () -> Seq Window -> X ()
|
||||||
focusNextMatchOrDo qry act = findM (runQuery qry)
|
focusNextMatchOrDo qry act = findM (runQuery qry)
|
||||||
>=> maybe act (windows . SS.focusWindow)
|
>=> maybe act (windows . SS.focusWindow)
|
||||||
|
|
||||||
-- Returns the list of windows ordered by workspace as specified in
|
-- Returns the list of windows ordered by workspace as specified in
|
||||||
@ -126,7 +126,7 @@ orderedWindowList History = liftM (\(HistoryDB w ws) -> maybe ws (ws |>) w) XS.g
|
|||||||
orderedWindowList dir = withWindowSet $ \ss -> do
|
orderedWindowList dir = withWindowSet $ \ss -> do
|
||||||
wsids <- asks (Seq.fromList . workspaces . config)
|
wsids <- asks (Seq.fromList . workspaces . config)
|
||||||
let wspcs = orderedWorkspaceList ss wsids
|
let wspcs = orderedWorkspaceList ss wsids
|
||||||
wins = dirfun dir
|
wins = dirfun dir
|
||||||
$ Fold.foldl' (><) Seq.empty
|
$ Fold.foldl' (><) Seq.empty
|
||||||
$ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs
|
$ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs
|
||||||
cur = SS.peek ss
|
cur = SS.peek ss
|
||||||
@ -148,7 +148,7 @@ orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
|
|||||||
--- History navigation, requires a layout modifier -------------------
|
--- History navigation, requires a layout modifier -------------------
|
||||||
|
|
||||||
-- The state extension that holds the history information
|
-- The state extension that holds the history information
|
||||||
data HistoryDB = HistoryDB (Maybe Window) -- currently focused window
|
data HistoryDB = HistoryDB (Maybe Window) -- currently focused window
|
||||||
(Seq Window) -- previously focused windows
|
(Seq Window) -- previously focused windows
|
||||||
deriving (Read, Show, Typeable)
|
deriving (Read, Show, Typeable)
|
||||||
|
|
||||||
@ -182,12 +182,12 @@ flt :: (a -> Bool) -> Seq a -> Seq a
|
|||||||
flt p = Fold.foldl (\xs x -> if p x then xs |> x else xs) Seq.empty
|
flt p = Fold.foldl (\xs x -> if p x then xs |> x else xs) Seq.empty
|
||||||
|
|
||||||
brkl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
|
brkl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
|
||||||
brkl p xs = flip Seq.splitAt xs
|
brkl p xs = flip Seq.splitAt xs
|
||||||
$ snd
|
$ snd
|
||||||
$ Fold.foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs
|
$ Fold.foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs
|
||||||
where
|
where
|
||||||
l = Seq.length xs
|
l = Seq.length xs
|
||||||
|
|
||||||
--- Some sequence helpers --------------------------------------------
|
--- Some sequence helpers --------------------------------------------
|
||||||
|
|
||||||
-- Rotates the sequence by one position
|
-- Rotates the sequence by one position
|
||||||
|
@ -9,7 +9,7 @@
|
|||||||
-- Stability : unstable
|
-- Stability : unstable
|
||||||
-- Portability : unportable
|
-- Portability : unportable
|
||||||
--
|
--
|
||||||
-- Remap Keybinding on the fly, e.g having Dvorak char, but everything with Control/Shift
|
-- Remap Keybinding on the fly, e.g having Dvorak char, but everything with Control/Shift
|
||||||
-- is left us Layout
|
-- is left us Layout
|
||||||
--
|
--
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
@ -42,7 +42,7 @@ instance ExtensionClass KeymapTable where
|
|||||||
-- $usage
|
-- $usage
|
||||||
-- Provides the possibility to remap parts of the keymap to generate different keys
|
-- Provides the possibility to remap parts of the keymap to generate different keys
|
||||||
--
|
--
|
||||||
-- * E.g You want to type Programmers Dvorak, but your keybindings should be the normal us layout
|
-- * E.g You want to type Programmers Dvorak, but your keybindings should be the normal us layout
|
||||||
-- after all
|
-- after all
|
||||||
--
|
--
|
||||||
-- First, you must add all possible keybindings for all layout you want to use:
|
-- First, you must add all possible keybindings for all layout you want to use:
|
||||||
|
@ -16,22 +16,22 @@
|
|||||||
|
|
||||||
module XMonad.Actions.Navigation2D ( -- * Usage
|
module XMonad.Actions.Navigation2D ( -- * Usage
|
||||||
-- $usage
|
-- $usage
|
||||||
|
|
||||||
-- * Finer points
|
-- * Finer points
|
||||||
-- $finer_points
|
-- $finer_points
|
||||||
|
|
||||||
-- * Alternative directional navigation modules
|
-- * Alternative directional navigation modules
|
||||||
-- $alternatives
|
-- $alternatives
|
||||||
|
|
||||||
-- * Incompatibilities
|
-- * Incompatibilities
|
||||||
-- $incompatibilities
|
-- $incompatibilities
|
||||||
|
|
||||||
-- * Detailed technical discussion
|
-- * Detailed technical discussion
|
||||||
-- $technical
|
-- $technical
|
||||||
|
|
||||||
-- * Exported functions and types
|
-- * Exported functions and types
|
||||||
-- #Exports#
|
-- #Exports#
|
||||||
|
|
||||||
withNavigation2DConfig
|
withNavigation2DConfig
|
||||||
, Navigation2DConfig(..)
|
, Navigation2DConfig(..)
|
||||||
, defaultNavigation2DConfig
|
, defaultNavigation2DConfig
|
||||||
@ -226,7 +226,7 @@ import XMonad.Util.Types
|
|||||||
|
|
||||||
-- | A rectangle paired with an object
|
-- | A rectangle paired with an object
|
||||||
type Rect a = (a, Rectangle)
|
type Rect a = (a, Rectangle)
|
||||||
|
|
||||||
-- | A shorthand for window-rectangle pairs. Reduces typing.
|
-- | A shorthand for window-rectangle pairs. Reduces typing.
|
||||||
type WinRect = Rect Window
|
type WinRect = Rect Window
|
||||||
|
|
||||||
@ -251,7 +251,7 @@ runNav (N _ nav) = nav
|
|||||||
type Generality = Int
|
type Generality = Int
|
||||||
|
|
||||||
instance Eq Navigation2D where
|
instance Eq Navigation2D where
|
||||||
(N x _) == (N y _) = x == y
|
(N x _) == (N y _) = x == y
|
||||||
|
|
||||||
instance Ord Navigation2D where
|
instance Ord Navigation2D where
|
||||||
(N x _) <= (N y _) = x <= y
|
(N x _) <= (N y _) = x <= y
|
||||||
@ -302,7 +302,7 @@ data Navigation2DConfig = Navigation2DConfig
|
|||||||
|
|
||||||
-- | Shorthand for the tedious screen type
|
-- | Shorthand for the tedious screen type
|
||||||
type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
|
type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
|
||||||
|
|
||||||
-- So we can store the configuration in extensible state
|
-- So we can store the configuration in extensible state
|
||||||
instance ExtensionClass Navigation2DConfig where
|
instance ExtensionClass Navigation2DConfig where
|
||||||
initialValue = defaultNavigation2DConfig
|
initialValue = defaultNavigation2DConfig
|
||||||
@ -755,7 +755,7 @@ wrapOffsets winset = (max_x - min_x, max_y - min_y)
|
|||||||
max_x = fi $ maximum $ map (\r -> rect_x r + (fi $ rect_width r)) rects
|
max_x = fi $ maximum $ map (\r -> rect_x r + (fi $ rect_width r)) rects
|
||||||
max_y = fi $ maximum $ map (\r -> rect_y r + (fi $ rect_height r)) rects
|
max_y = fi $ maximum $ map (\r -> rect_y r + (fi $ rect_height r)) rects
|
||||||
rects = map snd $ visibleWorkspaces winset False
|
rects = map snd $ visibleWorkspaces winset False
|
||||||
|
|
||||||
|
|
||||||
-- | Returns the list of screens sorted primarily by their centers'
|
-- | Returns the list of screens sorted primarily by their centers'
|
||||||
-- x-coordinates and secondarily by their y-coordinates.
|
-- x-coordinates and secondarily by their y-coordinates.
|
||||||
|
@ -3,11 +3,11 @@
|
|||||||
-- Module : XMonad.Actions.Workscreen
|
-- Module : XMonad.Actions.Workscreen
|
||||||
-- Copyright : (c) 2012 kedals0
|
-- Copyright : (c) 2012 kedals0
|
||||||
-- License : BSD3-style (see LICENSE)
|
-- License : BSD3-style (see LICENSE)
|
||||||
--
|
--
|
||||||
-- Maintainer : Dal <kedasl0@gmail.com>
|
-- Maintainer : Dal <kedasl0@gmail.com>
|
||||||
-- Stability : unstable
|
-- Stability : unstable
|
||||||
-- Portability: unportable
|
-- Portability: unportable
|
||||||
--
|
--
|
||||||
-- A workscreen permits to display a set of workspaces on several
|
-- A workscreen permits to display a set of workspaces on several
|
||||||
-- screens. In xinerama mode, when a workscreen is viewed, workspaces
|
-- screens. In xinerama mode, when a workscreen is viewed, workspaces
|
||||||
-- associated to all screens are visible.
|
-- associated to all screens are visible.
|
||||||
@ -48,7 +48,7 @@ import XMonad.Actions.OnScreen
|
|||||||
-- > return ()
|
-- > return ()
|
||||||
--
|
--
|
||||||
-- Then, replace normal workspace view and shift keybinding:
|
-- Then, replace normal workspace view and shift keybinding:
|
||||||
--
|
--
|
||||||
-- > [((m .|. modm, k), f i)
|
-- > [((m .|. modm, k), f i)
|
||||||
-- > | (i, k) <- zip [0..] [1..12]
|
-- > | (i, k) <- zip [0..] [1..12]
|
||||||
-- > , (f, m) <- [(Workscreen.viewWorkscreen, 0), (Workscreen.shiftToWorkscreen, shiftMask)]]
|
-- > , (f, m) <- [(Workscreen.viewWorkscreen, 0), (Workscreen.shiftToWorkscreen, shiftMask)]]
|
||||||
@ -67,7 +67,7 @@ instance ExtensionClass WorkscreenStorage where
|
|||||||
-- | Helper to group workspaces. Multiply workspace by screens number.
|
-- | Helper to group workspaces. Multiply workspace by screens number.
|
||||||
expandWorkspace :: Int -> [WorkspaceId] -> [WorkspaceId]
|
expandWorkspace :: Int -> [WorkspaceId] -> [WorkspaceId]
|
||||||
expandWorkspace nscr ws = concat $ map expandId ws
|
expandWorkspace nscr ws = concat $ map expandId ws
|
||||||
where expandId wsId = let t = wsId ++ "_"
|
where expandId wsId = let t = wsId ++ "_"
|
||||||
in map ((++) t . show ) [1..nscr]
|
in map ((++) t . show ) [1..nscr]
|
||||||
|
|
||||||
-- | Create workscreen list from workspace list. Group workspaces to
|
-- | Create workscreen list from workspace list. Group workspaces to
|
||||||
@ -95,7 +95,7 @@ viewWorkscreen wscrId = do (WorkscreenStorage c a) <- XS.get
|
|||||||
XS.put newWorkscreenStorage
|
XS.put newWorkscreenStorage
|
||||||
|
|
||||||
viewWorkscreen' :: Workscreen -> WindowSet -> WindowSet
|
viewWorkscreen' :: Workscreen -> WindowSet -> WindowSet
|
||||||
viewWorkscreen' (Workscreen _ ws) = \s -> foldl wsToSc' s (zip [0..] ws)
|
viewWorkscreen' (Workscreen _ ws) = \s -> foldl wsToSc' s (zip [0..] ws)
|
||||||
where wsToSc' s (scr,wsId) = greedyViewOnScreen scr wsId s
|
where wsToSc' s (scr,wsId) = greedyViewOnScreen scr wsId s
|
||||||
|
|
||||||
shiftWs :: [WorkspaceId] -> [WorkspaceId]
|
shiftWs :: [WorkspaceId] -> [WorkspaceId]
|
||||||
|
@ -45,7 +45,7 @@ import System.IO (hPutStrLn
|
|||||||
-- Logged key events look like:
|
-- Logged key events look like:
|
||||||
--
|
--
|
||||||
-- @keycode 53 sym 120 (0x78, "x") mask 0x0 () clean 0x0 ()@
|
-- @keycode 53 sym 120 (0x78, "x") mask 0x0 () clean 0x0 ()@
|
||||||
--
|
--
|
||||||
-- The @mask@ and @clean@ indicate the modifiers pressed along with
|
-- The @mask@ and @clean@ indicate the modifiers pressed along with
|
||||||
-- the key; @mask@ is raw, and @clean@ is what @xmonad@ sees after
|
-- the key; @mask@ is raw, and @clean@ is what @xmonad@ sees after
|
||||||
-- sanitizing it (removing @numberLockMask@, etc.)
|
-- sanitizing it (removing @numberLockMask@, etc.)
|
||||||
|
@ -105,7 +105,7 @@ import Graphics.X11.Xlib.Extras (Event(..))
|
|||||||
--
|
--
|
||||||
-- "XMonad.Doc.Extending#Editing_the_event_hook"
|
-- "XMonad.Doc.Extending#Editing_the_event_hook"
|
||||||
-- (which sadly doesnt exist at the time of writing...)
|
-- (which sadly doesnt exist at the time of writing...)
|
||||||
--
|
--
|
||||||
-- /WARNING:/ This module is very good at triggering bugs in
|
-- /WARNING:/ This module is very good at triggering bugs in
|
||||||
-- compositing managers. Symptoms range from windows not being
|
-- compositing managers. Symptoms range from windows not being
|
||||||
-- repainted until the compositing manager is restarted or the
|
-- repainted until the compositing manager is restarted or the
|
||||||
|
@ -20,7 +20,7 @@
|
|||||||
module XMonad.Hooks.ICCCMFocus
|
module XMonad.Hooks.ICCCMFocus
|
||||||
{-# DEPRECATED "XMonad.Hooks.ICCCMFocus: xmonad>0.10 core merged issue 177" #-}
|
{-# DEPRECATED "XMonad.Hooks.ICCCMFocus: xmonad>0.10 core merged issue 177" #-}
|
||||||
(
|
(
|
||||||
atom_WM_TAKE_FOCUS
|
atom_WM_TAKE_FOCUS
|
||||||
, takeFocusX
|
, takeFocusX
|
||||||
, takeTopFocus
|
, takeTopFocus
|
||||||
) where
|
) where
|
||||||
@ -38,5 +38,5 @@ takeFocusX _w = return ()
|
|||||||
takeTopFocus ::
|
takeTopFocus ::
|
||||||
X ()
|
X ()
|
||||||
takeTopFocus =
|
takeTopFocus =
|
||||||
(withWindowSet $ maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D"
|
(withWindowSet $ maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D"
|
||||||
|
|
||||||
|
@ -438,8 +438,8 @@ instance UrgencyHook FocusHook where
|
|||||||
--
|
--
|
||||||
-- > withUrgencyHookC BorderUrgencyHook { urgencyBorderColor = "#ff0000" } urgencyConfig { suppressWhen = Never } ...
|
-- > withUrgencyHookC BorderUrgencyHook { urgencyBorderColor = "#ff0000" } urgencyConfig { suppressWhen = Never } ...
|
||||||
--
|
--
|
||||||
-- (This should be @urgentBorderColor@ but that breaks "XMonad.Layout.Decoration".
|
-- (This should be @urgentBorderColor@ but that breaks "XMonad.Layout.Decoration".
|
||||||
-- @borderColor@ breaks anyone using 'XPConfig' from "XMonad.Prompt". We need to
|
-- @borderColor@ breaks anyone using 'XPConfig' from "XMonad.Prompt". We need to
|
||||||
-- think a bit more about namespacing issues, maybe.)
|
-- think a bit more about namespacing issues, maybe.)
|
||||||
|
|
||||||
borderUrgencyHook :: String -> Window -> X ()
|
borderUrgencyHook :: String -> Window -> X ()
|
||||||
|
@ -70,9 +70,9 @@ import Control.Monad (forM)
|
|||||||
-- group, and the layout with which the groups themselves will
|
-- group, and the layout with which the groups themselves will
|
||||||
-- be arranged on the screen.
|
-- be arranged on the screen.
|
||||||
--
|
--
|
||||||
-- The "XMonad.Layout.Groups.Examples" and "XMonad.Layout.Groups.Wmii"
|
-- The "XMonad.Layout.Groups.Examples" and "XMonad.Layout.Groups.Wmii"
|
||||||
-- modules contain examples of layouts that can be defined with this
|
-- modules contain examples of layouts that can be defined with this
|
||||||
-- combinator. They're also the recommended starting point
|
-- combinator. They're also the recommended starting point
|
||||||
-- if you are a beginner and looking for something you can use easily.
|
-- if you are a beginner and looking for something you can use easily.
|
||||||
--
|
--
|
||||||
-- One thing to note is that 'Groups'-based layout have their own
|
-- One thing to note is that 'Groups'-based layout have their own
|
||||||
@ -81,7 +81,7 @@ import Control.Monad (forM)
|
|||||||
-- will have no visible effect, and those like 'XMonad.StackSet.focusUp'
|
-- will have no visible effect, and those like 'XMonad.StackSet.focusUp'
|
||||||
-- will focus the windows in an unpredictable order. For a better way of
|
-- will focus the windows in an unpredictable order. For a better way of
|
||||||
-- rearranging windows and moving focus in such a layout, see the
|
-- rearranging windows and moving focus in such a layout, see the
|
||||||
-- example 'ModifySpec's (to be passed to the 'Modify' message) provided
|
-- example 'ModifySpec's (to be passed to the 'Modify' message) provided
|
||||||
-- by this module.
|
-- by this module.
|
||||||
--
|
--
|
||||||
-- If you use both 'Groups'-based and other layouts, The "XMonad.Layout.Groups.Helpers"
|
-- If you use both 'Groups'-based and other layouts, The "XMonad.Layout.Groups.Helpers"
|
||||||
@ -105,7 +105,7 @@ group l l2 = Groups l l2 startingGroups (U 1 0)
|
|||||||
data Uniq = U Integer Integer
|
data Uniq = U Integer Integer
|
||||||
deriving (Eq, Show, Read)
|
deriving (Eq, Show, Read)
|
||||||
|
|
||||||
-- | From a seed, generate an infinite list of keys and a new
|
-- | From a seed, generate an infinite list of keys and a new
|
||||||
-- seed. All keys generated with this method will be different
|
-- seed. All keys generated with this method will be different
|
||||||
-- provided you don't use 'gen' again with a key from the list.
|
-- provided you don't use 'gen' again with a key from the list.
|
||||||
-- (if you need to do that, see 'split' instead)
|
-- (if you need to do that, see 'split' instead)
|
||||||
@ -121,7 +121,7 @@ gen (U i1 i2) = (U (i1+1) i2, zipWith U (repeat i1) [i2..])
|
|||||||
|
|
||||||
-- | Add a unique identity to a layout so we can
|
-- | Add a unique identity to a layout so we can
|
||||||
-- follow it around.
|
-- follow it around.
|
||||||
data WithID l a = ID { getID :: Uniq
|
data WithID l a = ID { getID :: Uniq
|
||||||
, unID :: (l a)}
|
, unID :: (l a)}
|
||||||
deriving (Show, Read)
|
deriving (Show, Read)
|
||||||
|
|
||||||
@ -133,15 +133,15 @@ instance Eq (WithID l a) where
|
|||||||
ID id1 _ == ID id2 _ = id1 == id2
|
ID id1 _ == ID id2 _ = id1 == id2
|
||||||
|
|
||||||
instance LayoutClass l a => LayoutClass (WithID l) a where
|
instance LayoutClass l a => LayoutClass (WithID l) a where
|
||||||
runLayout ws@W.Workspace { W.layout = ID id l } r
|
runLayout ws@W.Workspace { W.layout = ID id l } r
|
||||||
= do (placements, ml') <- flip runLayout r
|
= do (placements, ml') <- flip runLayout r
|
||||||
ws { W.layout = l}
|
ws { W.layout = l}
|
||||||
return (placements, ID id <$> ml')
|
return (placements, ID id <$> ml')
|
||||||
handleMessage (ID id l) sm = do ml' <- handleMessage l sm
|
handleMessage (ID id l) sm = do ml' <- handleMessage l sm
|
||||||
return $ ID id <$> ml'
|
return $ ID id <$> ml'
|
||||||
description (ID _ l) = description l
|
description (ID _ l) = description l
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
-- * The 'Groups' layout
|
-- * The 'Groups' layout
|
||||||
|
|
||||||
@ -211,7 +211,7 @@ modifyGroups f g = let (seed', id:_) = gen (seed g)
|
|||||||
|
|
||||||
-- | Adapt our groups to a new stack.
|
-- | Adapt our groups to a new stack.
|
||||||
-- This algorithm handles window additions and deletions correctly,
|
-- This algorithm handles window additions and deletions correctly,
|
||||||
-- ignores changes in window ordering, and tries to react to any
|
-- ignores changes in window ordering, and tries to react to any
|
||||||
-- other stack changes as gracefully as possible.
|
-- other stack changes as gracefully as possible.
|
||||||
readapt :: Eq a => Zipper a -> Groups l l2 a -> Groups l l2 a
|
readapt :: Eq a => Zipper a -> Groups l l2 a -> Groups l l2 a
|
||||||
readapt z g = let mf = getFocusZ z
|
readapt z g = let mf = getFocusZ z
|
||||||
@ -233,7 +233,7 @@ removeDeleted :: Eq a => Zipper a -> Zipper a -> Zipper a
|
|||||||
removeDeleted z = filterZ_ (flip elemZ z)
|
removeDeleted z = filterZ_ (flip elemZ z)
|
||||||
|
|
||||||
-- | Identify the windows not already in a group.
|
-- | Identify the windows not already in a group.
|
||||||
findNewWindows :: Eq a => [a] -> Zipper (Group l a)
|
findNewWindows :: Eq a => [a] -> Zipper (Group l a)
|
||||||
-> (Zipper (Group l a), [a])
|
-> (Zipper (Group l a), [a])
|
||||||
findNewWindows as gs = (gs, foldrZ_ removePresent as gs)
|
findNewWindows as gs = (gs, foldrZ_ removePresent as gs)
|
||||||
where removePresent g as' = filter (not . flip elemZ (gZipper g)) as'
|
where removePresent g as' = filter (not . flip elemZ (gZipper g)) as'
|
||||||
@ -279,10 +279,10 @@ instance (LayoutClass l Window, LayoutClass l2 (Group l Window))
|
|||||||
|
|
||||||
let placements = concatMap fst results
|
let placements = concatMap fst results
|
||||||
newL = justMakeNew l mpart' (map snd results ++ hidden')
|
newL = justMakeNew l mpart' (map snd results ++ hidden')
|
||||||
|
|
||||||
return $ (placements, newL)
|
return $ (placements, newL)
|
||||||
|
|
||||||
handleMessage l@(Groups _ p _ _) sm | Just (ToEnclosing sm') <- fromMessage sm
|
handleMessage l@(Groups _ p _ _) sm | Just (ToEnclosing sm') <- fromMessage sm
|
||||||
= do mp' <- handleMessage p sm'
|
= do mp' <- handleMessage p sm'
|
||||||
return $ maybeMakeNew l mp' []
|
return $ maybeMakeNew l mp' []
|
||||||
|
|
||||||
@ -316,7 +316,7 @@ instance (LayoutClass l Window, LayoutClass l2 (Group l Window))
|
|||||||
step _ = return Nothing
|
step _ = return Nothing
|
||||||
|
|
||||||
|
|
||||||
justMakeNew :: Groups l l2 a -> Maybe (l2 (Group l a)) -> [Maybe (WithID l a)]
|
justMakeNew :: Groups l l2 a -> Maybe (l2 (Group l a)) -> [Maybe (WithID l a)]
|
||||||
-> Maybe (Groups l l2 a)
|
-> Maybe (Groups l l2 a)
|
||||||
justMakeNew g mpart' ml's = Just g { partitioner = fromMaybe (partitioner g) mpart'
|
justMakeNew g mpart' ml's = Just g { partitioner = fromMaybe (partitioner g) mpart'
|
||||||
, groups = combine (groups g) ml's }
|
, groups = combine (groups g) ml's }
|
||||||
@ -339,7 +339,7 @@ refocus g = case getFocusZ $ gZipper $ W.focus $ groups g
|
|||||||
|
|
||||||
-- ** ModifySpec type
|
-- ** ModifySpec type
|
||||||
|
|
||||||
-- | Type of functions describing modifications to a 'Groups' layout. They
|
-- | Type of functions describing modifications to a 'Groups' layout. They
|
||||||
-- are transformations on 'Zipper's of groups.
|
-- are transformations on 'Zipper's of groups.
|
||||||
--
|
--
|
||||||
-- Things you shouldn't do:
|
-- Things you shouldn't do:
|
||||||
@ -358,7 +358,7 @@ refocus g = case getFocusZ $ gZipper $ W.focus $ groups g
|
|||||||
-- 'ModifySpec's as arguments, or returning them, you'll need to write a type
|
-- 'ModifySpec's as arguments, or returning them, you'll need to write a type
|
||||||
-- signature and add @{-# LANGUAGE Rank2Types #-}@ at the beginning
|
-- signature and add @{-# LANGUAGE Rank2Types #-}@ at the beginning
|
||||||
type ModifySpec = forall l. WithID l Window
|
type ModifySpec = forall l. WithID l Window
|
||||||
-> Zipper (Group l Window)
|
-> Zipper (Group l Window)
|
||||||
-> Zipper (Group l Window)
|
-> Zipper (Group l Window)
|
||||||
|
|
||||||
-- | Apply a ModifySpec.
|
-- | Apply a ModifySpec.
|
||||||
@ -367,7 +367,7 @@ applySpec f g = let (seed', id:ids) = gen $ seed g
|
|||||||
g' = flip modifyGroups g $ f (ID id $ baseLayout g)
|
g' = flip modifyGroups g $ f (ID id $ baseLayout g)
|
||||||
>>> toTags
|
>>> toTags
|
||||||
>>> foldr reID ((ids, []), [])
|
>>> foldr reID ((ids, []), [])
|
||||||
>>> snd
|
>>> snd
|
||||||
>>> fromTags
|
>>> fromTags
|
||||||
in case groups g == groups g' of
|
in case groups g == groups g' of
|
||||||
True -> Nothing
|
True -> Nothing
|
||||||
@ -448,7 +448,7 @@ _removeFocused (W.Stack f [] []) = (f, Nothing)
|
|||||||
|
|
||||||
-- helper
|
-- helper
|
||||||
_moveToNewGroup :: WithID l Window -> W.Stack (Group l Window)
|
_moveToNewGroup :: WithID l Window -> W.Stack (Group l Window)
|
||||||
-> (Group l Window -> Zipper (Group l Window)
|
-> (Group l Window -> Zipper (Group l Window)
|
||||||
-> Zipper (Group l Window))
|
-> Zipper (Group l Window))
|
||||||
-> Zipper (Group l Window)
|
-> Zipper (Group l Window)
|
||||||
_moveToNewGroup l0 s insertX | G l (Just f) <- W.focus s
|
_moveToNewGroup l0 s insertX | G l (Just f) <- W.focus s
|
||||||
@ -456,7 +456,7 @@ _moveToNewGroup l0 s insertX | G l (Just f) <- W.focus s
|
|||||||
s' = s { W.focus = G l f' }
|
s' = s { W.focus = G l f' }
|
||||||
in insertX (G l0 $ singletonZ w) $ Just s'
|
in insertX (G l0 $ singletonZ w) $ Just s'
|
||||||
_moveToNewGroup _ s _ = Just s
|
_moveToNewGroup _ s _ = Just s
|
||||||
|
|
||||||
-- | Move the focused window to a new group before the current one.
|
-- | Move the focused window to a new group before the current one.
|
||||||
moveToNewGroupUp :: ModifySpec
|
moveToNewGroupUp :: ModifySpec
|
||||||
moveToNewGroupUp _ Nothing = Nothing
|
moveToNewGroupUp _ Nothing = Nothing
|
||||||
|
@ -67,12 +67,12 @@ import XMonad.Layout.Simplest
|
|||||||
|
|
||||||
|
|
||||||
-- $usage
|
-- $usage
|
||||||
-- This module contains example 'G.Groups'-based layouts.
|
-- This module contains example 'G.Groups'-based layouts.
|
||||||
-- You can either import this module directly, or look at its source
|
-- You can either import this module directly, or look at its source
|
||||||
-- for ideas of how "XMonad.Layout.Groups" may be used.
|
-- for ideas of how "XMonad.Layout.Groups" may be used.
|
||||||
--
|
--
|
||||||
-- You can use the contents of this module by adding
|
-- You can use the contents of this module by adding
|
||||||
--
|
--
|
||||||
-- > import XMonad.Layout.Groups.Examples
|
-- > import XMonad.Layout.Groups.Examples
|
||||||
--
|
--
|
||||||
-- to the top of your @.\/.xmonad\/xmonad.hs@.
|
-- to the top of your @.\/.xmonad\/xmonad.hs@.
|
||||||
@ -80,10 +80,10 @@ import XMonad.Layout.Simplest
|
|||||||
-- For more information on using any of the layouts, jump directly
|
-- For more information on using any of the layouts, jump directly
|
||||||
-- to its \"Example\" section.
|
-- to its \"Example\" section.
|
||||||
--
|
--
|
||||||
-- Whichever layout you choose to use, you will probably want to be
|
-- Whichever layout you choose to use, you will probably want to be
|
||||||
-- able to move focus and windows between groups in a consistent
|
-- able to move focus and windows between groups in a consistent
|
||||||
-- manner. For this, you should take a look at the functions from
|
-- manner. For this, you should take a look at the functions from
|
||||||
-- the "XMonad.Layout.Groups.Helpers" module, which are all
|
-- the "XMonad.Layout.Groups.Helpers" module, which are all
|
||||||
-- re-exported by this module.
|
-- re-exported by this module.
|
||||||
--
|
--
|
||||||
-- For more information on how to extend your layour hook and key bindings, see
|
-- For more information on how to extend your layour hook and key bindings, see
|
||||||
@ -99,7 +99,7 @@ data GroupEQ a = GroupEQ
|
|||||||
instance Eq a => EQF GroupEQ (G.Group l a) where
|
instance Eq a => EQF GroupEQ (G.Group l a) where
|
||||||
eq _ (G.G l1 _) (G.G l2 _) = G.sameID l1 l2
|
eq _ (G.G l1 _) (G.G l2 _) = G.sameID l1 l2
|
||||||
|
|
||||||
zoomRowG :: (Eq a, Show a, Read a, Show (l a), Read (l a))
|
zoomRowG :: (Eq a, Show a, Read a, Show (l a), Read (l a))
|
||||||
=> ZoomRow GroupEQ (G.Group l a)
|
=> ZoomRow GroupEQ (G.Group l a)
|
||||||
zoomRowG = zoomRowWith GroupEQ
|
zoomRowG = zoomRowWith GroupEQ
|
||||||
|
|
||||||
@ -171,10 +171,10 @@ toggleWindowFull = sendMessage ZoomFullToggle
|
|||||||
|
|
||||||
-- $example2
|
-- $example2
|
||||||
-- A layout which arranges windows into tabbed groups, and the groups
|
-- A layout which arranges windows into tabbed groups, and the groups
|
||||||
-- themselves according to XMonad's default algorithm
|
-- themselves according to XMonad's default algorithm
|
||||||
-- (@'Tall' ||| 'Mirror' 'Tall' ||| 'Full'@). As their names
|
-- (@'Tall' ||| 'Mirror' 'Tall' ||| 'Full'@). As their names
|
||||||
-- indicate, 'tallTabs' starts as 'Tall', 'mirrorTallTabs' starts
|
-- indicate, 'tallTabs' starts as 'Tall', 'mirrorTallTabs' starts
|
||||||
-- as 'Mirror' 'Tall' and 'fullTabs' starts as 'Full', but in any
|
-- as 'Mirror' 'Tall' and 'fullTabs' starts as 'Full', but in any
|
||||||
-- case you can freely switch between the three afterwards.
|
-- case you can freely switch between the three afterwards.
|
||||||
--
|
--
|
||||||
-- You can use any of these three layouts by including it in your layout hook.
|
-- You can use any of these three layouts by including it in your layout hook.
|
||||||
@ -204,7 +204,7 @@ data TiledTabsConfig s = TTC { vNMaster :: Int
|
|||||||
defaultTiledTabsConfig :: TiledTabsConfig DefaultShrinker
|
defaultTiledTabsConfig :: TiledTabsConfig DefaultShrinker
|
||||||
defaultTiledTabsConfig = TTC 1 0.5 (3/100) 1 0.5 (3/100) shrinkText defaultTheme
|
defaultTiledTabsConfig = TTC 1 0.5 (3/100) 1 0.5 (3/100) shrinkText defaultTheme
|
||||||
|
|
||||||
fullTabs c = _tab c $ G.group _tabs $ Full ||| _vert c ||| _horiz c
|
fullTabs c = _tab c $ G.group _tabs $ Full ||| _vert c ||| _horiz c
|
||||||
|
|
||||||
tallTabs c = _tab c $ G.group _tabs $ _vert c ||| _horiz c ||| Full
|
tallTabs c = _tab c $ G.group _tabs $ _vert c ||| _horiz c ||| Full
|
||||||
|
|
||||||
|
@ -69,7 +69,7 @@ import qualified Data.Map as M
|
|||||||
-- This module provides actions that try to send 'G.GroupsMessage's, and
|
-- This module provides actions that try to send 'G.GroupsMessage's, and
|
||||||
-- fall back to the classic way if the current layout doesn't hande them.
|
-- fall back to the classic way if the current layout doesn't hande them.
|
||||||
-- They are in the section called \"Layout-generic actions\".
|
-- They are in the section called \"Layout-generic actions\".
|
||||||
--
|
--
|
||||||
-- The sections \"Groups-specific actions\" contains actions that don't make
|
-- The sections \"Groups-specific actions\" contains actions that don't make
|
||||||
-- sense for non-'G.Groups'-based layouts. These are simply wrappers around
|
-- sense for non-'G.Groups'-based layouts. These are simply wrappers around
|
||||||
-- the equivalent 'G.GroupsMessage's, but are included so you don't have to
|
-- the equivalent 'G.GroupsMessage's, but are included so you don't have to
|
||||||
@ -139,7 +139,7 @@ ifFloat x1 x2 = withFocused $ \w -> do floats <- getFloats
|
|||||||
|
|
||||||
focusNonFloat :: X ()
|
focusNonFloat :: X ()
|
||||||
focusNonFloat = alt2 G.Refocus helper
|
focusNonFloat = alt2 G.Refocus helper
|
||||||
where helper = withFocused $ \w -> do
|
where helper = withFocused $ \w -> do
|
||||||
ws <- getWindows
|
ws <- getWindows
|
||||||
floats <- getFloats
|
floats <- getFloats
|
||||||
let (before, after) = span (/=w) ws
|
let (before, after) = span (/=w) ws
|
||||||
@ -170,7 +170,7 @@ focusNonFloatDown = alt2 (G.Modify G.focusDown) $ focusHelper not id
|
|||||||
|
|
||||||
focusFloatUp :: X ()
|
focusFloatUp :: X ()
|
||||||
focusFloatUp = focusHelper id reverse
|
focusFloatUp = focusHelper id reverse
|
||||||
|
|
||||||
focusFloatDown :: X ()
|
focusFloatDown :: X ()
|
||||||
focusFloatDown = focusHelper id id
|
focusFloatDown = focusHelper id id
|
||||||
|
|
||||||
|
@ -17,7 +17,7 @@
|
|||||||
|
|
||||||
module XMonad.Layout.Groups.Wmii ( -- * Usage
|
module XMonad.Layout.Groups.Wmii ( -- * Usage
|
||||||
-- $usage
|
-- $usage
|
||||||
|
|
||||||
wmii
|
wmii
|
||||||
, zoomGroupIn
|
, zoomGroupIn
|
||||||
, zoomGroupOut
|
, zoomGroupOut
|
||||||
@ -48,9 +48,9 @@ import XMonad.Layout.Simplest
|
|||||||
|
|
||||||
|
|
||||||
-- $usage
|
-- $usage
|
||||||
-- This module provides a layout inspired by the one used by the wmii
|
-- This module provides a layout inspired by the one used by the wmii
|
||||||
-- (<http://wmii.suckless.org>) window manager.
|
-- (<http://wmii.suckless.org>) window manager.
|
||||||
-- Windows are arranged into groups in a horizontal row, and each group can lay out
|
-- Windows are arranged into groups in a horizontal row, and each group can lay out
|
||||||
-- its windows
|
-- its windows
|
||||||
--
|
--
|
||||||
-- * by maximizing the focused one
|
-- * by maximizing the focused one
|
||||||
@ -59,16 +59,16 @@ import XMonad.Layout.Simplest
|
|||||||
--
|
--
|
||||||
-- * by arranging them in a column.
|
-- * by arranging them in a column.
|
||||||
--
|
--
|
||||||
-- As the groups are arranged in a 'ZoomRow', the relative width of each group can be
|
-- As the groups are arranged in a 'ZoomRow', the relative width of each group can be
|
||||||
-- increased or decreased at will. Groups can also be set to use the whole screen
|
-- increased or decreased at will. Groups can also be set to use the whole screen
|
||||||
-- whenever they have focus.
|
-- whenever they have focus.
|
||||||
--
|
--
|
||||||
-- You can use the contents of this module by adding
|
-- You can use the contents of this module by adding
|
||||||
--
|
--
|
||||||
-- > import XMonad.Layout.Groups.Wmii
|
-- > import XMonad.Layout.Groups.Wmii
|
||||||
--
|
--
|
||||||
-- to the top of your @.\/.xmonad\/xmonad.hs@, and adding 'wmii'
|
-- to the top of your @.\/.xmonad\/xmonad.hs@, and adding 'wmii'
|
||||||
-- (with a 'Shrinker' and decoration 'Theme' as
|
-- (with a 'Shrinker' and decoration 'Theme' as
|
||||||
-- parameters) to your layout hook, for example:
|
-- parameters) to your layout hook, for example:
|
||||||
--
|
--
|
||||||
-- > myLayout = wmii shrinkText defaultTheme
|
-- > myLayout = wmii shrinkText defaultTheme
|
||||||
@ -92,10 +92,10 @@ import XMonad.Layout.Simplest
|
|||||||
wmii s t = G.group innerLayout zoomRowG
|
wmii s t = G.group innerLayout zoomRowG
|
||||||
where column = named "Column" $ Tall 0 (3/100) (1/2)
|
where column = named "Column" $ Tall 0 (3/100) (1/2)
|
||||||
tabs = named "Tabs" $ Simplest
|
tabs = named "Tabs" $ Simplest
|
||||||
innerLayout = renamed [CutWordsLeft 3]
|
innerLayout = renamed [CutWordsLeft 3]
|
||||||
$ addTabs s t
|
$ addTabs s t
|
||||||
$ ignore NextLayout
|
$ ignore NextLayout
|
||||||
$ ignore (JumpToLayout "") $ unEscape
|
$ ignore (JumpToLayout "") $ unEscape
|
||||||
$ column ||| tabs ||| Full
|
$ column ||| tabs ||| Full
|
||||||
|
|
||||||
-- | Increase the width of the focused group
|
-- | Increase the width of the focused group
|
||||||
|
@ -140,7 +140,7 @@ closeButton' = [[1,1,0,0,0,0,0,0,1,1],
|
|||||||
|
|
||||||
|
|
||||||
closeButton :: [[Bool]]
|
closeButton :: [[Bool]]
|
||||||
closeButton = convertToBool closeButton'
|
closeButton = convertToBool closeButton'
|
||||||
|
|
||||||
-- | A function intended to be plugged into the 'decorationCatchClicksHook' of a decoration.
|
-- | A function intended to be plugged into the 'decorationCatchClicksHook' of a decoration.
|
||||||
-- It will intercept clicks on the buttons of the decoration and invoke the associated action.
|
-- It will intercept clicks on the buttons of the decoration and invoke the associated action.
|
||||||
|
@ -40,7 +40,7 @@ import qualified XMonad.Layout.LayoutBuilder as B
|
|||||||
--
|
--
|
||||||
-- compare "XMonad.Util.Invisible"
|
-- compare "XMonad.Util.Invisible"
|
||||||
|
|
||||||
-- | Type class for predicates. This enables us to manage not only Windows,
|
-- | Type class for predicates. This enables us to manage not only Windows,
|
||||||
-- but any objects, for which instance Predicate is defined.
|
-- but any objects, for which instance Predicate is defined.
|
||||||
--
|
--
|
||||||
-- Another instance exists in XMonad.Util.WindowPropertiesRE in xmonad-extras
|
-- Another instance exists in XMonad.Util.WindowPropertiesRE in xmonad-extras
|
||||||
|
@ -24,7 +24,7 @@ import XMonad
|
|||||||
import XMonad.Layout.LayoutModifier
|
import XMonad.Layout.LayoutModifier
|
||||||
|
|
||||||
-- $usage
|
-- $usage
|
||||||
-- You can use this module by adding
|
-- You can use this module by adding
|
||||||
--
|
--
|
||||||
-- > import XMonad.Layout.Renamed
|
-- > import XMonad.Layout.Renamed
|
||||||
--
|
--
|
||||||
|
@ -42,7 +42,7 @@ import XMonad.Layout.Decoration (fi)
|
|||||||
|
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Control.Arrow (second)
|
import Control.Arrow (second)
|
||||||
|
|
||||||
-- $usage
|
-- $usage
|
||||||
-- This module provides a layout which places all windows in a single
|
-- This module provides a layout which places all windows in a single
|
||||||
-- row; the size occupied by each individual window can be increased
|
-- row; the size occupied by each individual window can be increased
|
||||||
@ -80,9 +80,9 @@ zoomRow :: (Eq a, Show a, Read a) => ZoomRow ClassEQ a
|
|||||||
zoomRow = ZC ClassEQ emptyZ
|
zoomRow = ZC ClassEQ emptyZ
|
||||||
|
|
||||||
-- $noneq
|
-- $noneq
|
||||||
-- Haskell's 'Eq' class is usually concerned with structural equality, whereas
|
-- Haskell's 'Eq' class is usually concerned with structural equality, whereas
|
||||||
-- what this layout really wants is for its elements to have a unique identity,
|
-- what this layout really wants is for its elements to have a unique identity,
|
||||||
-- even across changes. There are cases (such as, importantly, 'Window's) where
|
-- even across changes. There are cases (such as, importantly, 'Window's) where
|
||||||
-- the 'Eq' instance for a type actually does that, but if you want to lay
|
-- the 'Eq' instance for a type actually does that, but if you want to lay
|
||||||
-- out something more exotic than windows and your 'Eq' means something else,
|
-- out something more exotic than windows and your 'Eq' means something else,
|
||||||
-- you can use the following.
|
-- you can use the following.
|
||||||
@ -92,7 +92,7 @@ zoomRow = ZC ClassEQ emptyZ
|
|||||||
-- sure that the layout never has to handle two \"equal\" elements
|
-- sure that the layout never has to handle two \"equal\" elements
|
||||||
-- at the same time (it won't do any huge damage, but might behave
|
-- at the same time (it won't do any huge damage, but might behave
|
||||||
-- a bit strangely).
|
-- a bit strangely).
|
||||||
zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a)
|
zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a)
|
||||||
=> f a -> ZoomRow f a
|
=> f a -> ZoomRow f a
|
||||||
zoomRowWith f = ZC f emptyZ
|
zoomRowWith f = ZC f emptyZ
|
||||||
|
|
||||||
@ -185,7 +185,7 @@ zoomReset = ZoomTo 1
|
|||||||
|
|
||||||
-- * LayoutClass instance
|
-- * LayoutClass instance
|
||||||
|
|
||||||
instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
|
instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
|
||||||
=> LayoutClass (ZoomRow f) a where
|
=> LayoutClass (ZoomRow f) a where
|
||||||
description (ZC _ Nothing) = "ZoomRow"
|
description (ZC _ Nothing) = "ZoomRow"
|
||||||
description (ZC _ (Just s)) = "ZoomRow" ++ if full $ W.focus s
|
description (ZC _ (Just s)) = "ZoomRow" ++ if full $ W.focus s
|
||||||
@ -197,7 +197,7 @@ instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
|
|||||||
|
|
||||||
doLayout (ZC f zelts) r@(Rectangle _ _ w _) s
|
doLayout (ZC f zelts) r@(Rectangle _ _ w _) s
|
||||||
= let elts = W.integrate' zelts
|
= let elts = W.integrate' zelts
|
||||||
zelts' = mapZ_ (\a -> fromMaybe (E a 1 False)
|
zelts' = mapZ_ (\a -> fromMaybe (E a 1 False)
|
||||||
$ lookupBy (eq f) a elts) $ Just s
|
$ lookupBy (eq f) a elts) $ Just s
|
||||||
elts' = W.integrate' zelts'
|
elts' = W.integrate' zelts'
|
||||||
|
|
||||||
@ -251,7 +251,7 @@ instance (EQF f a, Show a, Read a, Show (f a), Read (f a))
|
|||||||
= case fromMessage sm of
|
= case fromMessage sm of
|
||||||
Just (Zoom r') -> Just $ ZC f $ setFocus zelts $ E a (r*r') b
|
Just (Zoom r') -> Just $ ZC f $ setFocus zelts $ E a (r*r') b
|
||||||
Just (ZoomTo r') -> Just $ ZC f $ setFocus zelts $ E a r' b
|
Just (ZoomTo r') -> Just $ ZC f $ setFocus zelts $ E a r' b
|
||||||
Just ZoomFullToggle -> pureMessage (ZC f zelts)
|
Just ZoomFullToggle -> pureMessage (ZC f zelts)
|
||||||
$ SomeMessage $ ZoomFull $ not b
|
$ SomeMessage $ ZoomFull $ not b
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
|
@ -29,7 +29,7 @@ data Placement = OffsetLeft Int Int -- ^ An exact amount of pixels from the up
|
|||||||
| CenterLeft Int -- ^ Centered in the y-axis, an amount of pixels from the left
|
| CenterLeft Int -- ^ Centered in the y-axis, an amount of pixels from the left
|
||||||
| CenterRight Int -- ^ Centered in the y-axis, an amount of pixels from the right
|
| CenterRight Int -- ^ Centered in the y-axis, an amount of pixels from the right
|
||||||
deriving (Show, Read)
|
deriving (Show, Read)
|
||||||
|
|
||||||
-- $usage
|
-- $usage
|
||||||
-- This module uses matrices of boolean values as images. When drawing them,
|
-- This module uses matrices of boolean values as images. When drawing them,
|
||||||
-- a True value tells that we want the fore color, and a False value that we
|
-- a True value tells that we want the fore color, and a False value that we
|
||||||
|
@ -145,7 +145,7 @@ swapUpZ (Just s) = Just s { W.up = reverse (W.down s), W.down = [] }
|
|||||||
swapDownZ :: Zipper a -> Zipper a
|
swapDownZ :: Zipper a -> Zipper a
|
||||||
swapDownZ Nothing = Nothing
|
swapDownZ Nothing = Nothing
|
||||||
swapDownZ (Just s) | d:down <- W.down s = Just s { W.down = down, W.up = d:W.up s }
|
swapDownZ (Just s) | d:down <- W.down s = Just s { W.down = down, W.up = d:W.up s }
|
||||||
swapDownZ (Just s) = Just s { W.up = [], W.down = reverse (W.up s) }
|
swapDownZ (Just s) = Just s { W.up = [], W.down = reverse (W.up s) }
|
||||||
|
|
||||||
-- | Swap the focused element with the first one
|
-- | Swap the focused element with the first one
|
||||||
swapMasterZ :: Zipper a -> Zipper a
|
swapMasterZ :: Zipper a -> Zipper a
|
||||||
@ -197,7 +197,7 @@ sortByZ f = fromTags . sortBy (adapt f) . toTags
|
|||||||
where adapt g e1 e2 = g (fromE e1) (fromE e2)
|
where adapt g e1 e2 = g (fromE e1) (fromE e2)
|
||||||
|
|
||||||
-- ** Maps
|
-- ** Maps
|
||||||
|
|
||||||
-- | Map a function over a stack. The boolean argument indcates whether
|
-- | Map a function over a stack. The boolean argument indcates whether
|
||||||
-- the current element is the focused one
|
-- the current element is the focused one
|
||||||
mapZ :: (Bool -> a -> b) -> Zipper a -> Zipper b
|
mapZ :: (Bool -> a -> b) -> Zipper a -> Zipper b
|
||||||
|
@ -82,7 +82,7 @@ promptSelection = unsafePromptSelection
|
|||||||
safePromptSelection app = join $ io $ liftM (safeSpawn app . return) getSelection
|
safePromptSelection app = join $ io $ liftM (safeSpawn app . return) getSelection
|
||||||
unsafePromptSelection app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " " ++ x) getSelection
|
unsafePromptSelection app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " " ++ x) getSelection
|
||||||
|
|
||||||
{- | A wrapper around 'promptSelection' and its safe variant. They take two parameters, the
|
{- | A wrapper around 'promptSelection' and its safe variant. They take two parameters, the
|
||||||
first is a function that transforms strings, and the second is the application to run.
|
first is a function that transforms strings, and the second is the application to run.
|
||||||
The transformer essentially transforms the selection in X.
|
The transformer essentially transforms the selection in X.
|
||||||
One example is to wrap code, such as a command line action copied out of the browser
|
One example is to wrap code, such as a command line action copied out of the browser
|
||||||
|
@ -38,7 +38,7 @@ import XMonad.Util.Image
|
|||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
|
||||||
-- $usage
|
-- $usage
|
||||||
-- See "XMonad.Layout.Tabbed" or "XMonad.Layout.DragPane" or
|
-- See "XMonad.Layout.Tabbed" or "XMonad.Layout.DragPane" or
|
||||||
-- "XMonad.Layout.Decoration" for usage examples
|
-- "XMonad.Layout.Decoration" for usage examples
|
||||||
|
|
||||||
-- | Compute the weighted average the colors of two given Pixel values.
|
-- | Compute the weighted average the colors of two given Pixel values.
|
||||||
@ -163,7 +163,7 @@ paintTextAndIcons w fs wh ht bw bc borc ffc fbc als strs i_als icons = do
|
|||||||
-- drawn inside it.
|
-- drawn inside it.
|
||||||
-- Not exported.
|
-- Not exported.
|
||||||
paintWindow' :: Window -> Rectangle -> Dimension -> String -> String
|
paintWindow' :: Window -> Rectangle -> Dimension -> String -> String
|
||||||
-> Maybe (XMonadFont,String,String,[(String, (Position, Position))])
|
-> Maybe (XMonadFont,String,String,[(String, (Position, Position))])
|
||||||
-> Maybe (String, String, [((Position, Position), [[Bool]])]) -> X ()
|
-> Maybe (String, String, [((Position, Position), [[Bool]])]) -> X ()
|
||||||
paintWindow' win (Rectangle _ _ wh ht) bw color b_color strStuff iconStuff = do
|
paintWindow' win (Rectangle _ _ wh ht) bw color b_color strStuff iconStuff = do
|
||||||
d <- asks display
|
d <- asks display
|
||||||
|
Loading…
x
Reference in New Issue
Block a user