aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2012-11-09 02:41:56 +0100
committerAdam Vogt <vogt.adam@gmail.com>2012-11-09 02:41:56 +0100
commit3147065b3ff8d0cade905909aa29946378298f76 (patch)
tree7a3b0d4a08853e43b3ee95873466cefb2b48c567 /XMonad/Actions
parent7f324e08476792e522987867c0f8098eeb0e50e0 (diff)
downloadXMonadContrib-3147065b3ff8d0cade905909aa29946378298f76.tar.gz
XMonadContrib-3147065b3ff8d0cade905909aa29946378298f76.tar.xz
XMonadContrib-3147065b3ff8d0cade905909aa29946378298f76.zip
Remove trailing whitespace.
Ignore-this: 72e3afb6e6df47c51262006601765365 darcs-hash:20121109014156-1499c-45797b245e25e966e4ca337ee224b593aaac63a0.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/GroupNavigation.hs16
-rw-r--r--XMonad/Actions/KeyRemap.hs4
-rw-r--r--XMonad/Actions/Navigation2D.hs18
-rw-r--r--XMonad/Actions/Workscreen.hs10
4 files changed, 24 insertions, 24 deletions
diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs
index 8a43cd2..639876b 100644
--- a/XMonad/Actions/GroupNavigation.hs
+++ b/XMonad/Actions/GroupNavigation.hs
@@ -20,7 +20,7 @@
--
----------------------------------------------------------------------
-module XMonad.Actions.GroupNavigation ( -- * Usage
+module XMonad.Actions.GroupNavigation ( -- * Usage
-- $usage
Direction (..)
, nextMatch
@@ -110,13 +110,13 @@ nextMatch dir qry = nextMatchOrDo dir qry (return ())
-- | Focuses the next window that matches the given boolean query. If
-- there is no such window, perform the given action instead.
nextMatchOrDo :: Direction -> Query Bool -> X () -> X ()
-nextMatchOrDo dir qry act = orderedWindowList dir
+nextMatchOrDo dir qry act = orderedWindowList dir
>>= focusNextMatchOrDo qry act
-- Produces the action to perform depending on whether there's a
-- matching window
focusNextMatchOrDo :: Query Bool -> X () -> Seq Window -> X ()
-focusNextMatchOrDo qry act = findM (runQuery qry)
+focusNextMatchOrDo qry act = findM (runQuery qry)
>=> maybe act (windows . SS.focusWindow)
-- 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
wsids <- asks (Seq.fromList . workspaces . config)
let wspcs = orderedWorkspaceList ss wsids
- wins = dirfun dir
+ wins = dirfun dir
$ Fold.foldl' (><) Seq.empty
$ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs
cur = SS.peek ss
@@ -148,7 +148,7 @@ orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
--- History navigation, requires a layout modifier -------------------
-- 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
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
brkl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
-brkl p xs = flip Seq.splitAt xs
- $ snd
+brkl p xs = flip Seq.splitAt xs
+ $ snd
$ Fold.foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs
where
l = Seq.length xs
-
+
--- Some sequence helpers --------------------------------------------
-- Rotates the sequence by one position
diff --git a/XMonad/Actions/KeyRemap.hs b/XMonad/Actions/KeyRemap.hs
index 22c48ff..1fe953f 100644
--- a/XMonad/Actions/KeyRemap.hs
+++ b/XMonad/Actions/KeyRemap.hs
@@ -9,7 +9,7 @@
-- Stability : unstable
-- 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
--
-----------------------------------------------------------------------------
@@ -42,7 +42,7 @@ instance ExtensionClass KeymapTable where
-- $usage
-- 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
--
-- First, you must add all possible keybindings for all layout you want to use:
diff --git a/XMonad/Actions/Navigation2D.hs b/XMonad/Actions/Navigation2D.hs
index 835512c..27d772b 100644
--- a/XMonad/Actions/Navigation2D.hs
+++ b/XMonad/Actions/Navigation2D.hs
@@ -16,22 +16,22 @@
module XMonad.Actions.Navigation2D ( -- * Usage
-- $usage
-
+
-- * Finer points
-- $finer_points
-
+
-- * Alternative directional navigation modules
-- $alternatives
-
+
-- * Incompatibilities
-- $incompatibilities
-
+
-- * Detailed technical discussion
-- $technical
-- * Exported functions and types
-- #Exports#
-
+
withNavigation2DConfig
, Navigation2DConfig(..)
, defaultNavigation2DConfig
@@ -226,7 +226,7 @@ import XMonad.Util.Types
-- | A rectangle paired with an object
type Rect a = (a, Rectangle)
-
+
-- | A shorthand for window-rectangle pairs. Reduces typing.
type WinRect = Rect Window
@@ -251,7 +251,7 @@ runNav (N _ nav) = nav
type Generality = Int
instance Eq Navigation2D where
- (N x _) == (N y _) = x == y
+ (N x _) == (N y _) = x == y
instance Ord Navigation2D where
(N x _) <= (N y _) = x <= y
@@ -302,7 +302,7 @@ data Navigation2DConfig = Navigation2DConfig
-- | Shorthand for the tedious screen type
type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-
+
-- So we can store the configuration in extensible state
instance ExtensionClass Navigation2DConfig where
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_y = fi $ maximum $ map (\r -> rect_y r + (fi $ rect_height r)) rects
rects = map snd $ visibleWorkspaces winset False
-
+
-- | Returns the list of screens sorted primarily by their centers'
-- x-coordinates and secondarily by their y-coordinates.
diff --git a/XMonad/Actions/Workscreen.hs b/XMonad/Actions/Workscreen.hs
index 80f1b37..365ef4b 100644
--- a/XMonad/Actions/Workscreen.hs
+++ b/XMonad/Actions/Workscreen.hs
@@ -3,11 +3,11 @@
-- Module : XMonad.Actions.Workscreen
-- Copyright : (c) 2012 kedals0
-- License : BSD3-style (see LICENSE)
---
+--
-- Maintainer : Dal <kedasl0@gmail.com>
-- Stability : unstable
-- Portability: unportable
---
+--
-- A workscreen permits to display a set of workspaces on several
-- screens. In xinerama mode, when a workscreen is viewed, workspaces
-- associated to all screens are visible.
@@ -48,7 +48,7 @@ import XMonad.Actions.OnScreen
-- > return ()
--
-- Then, replace normal workspace view and shift keybinding:
---
+--
-- > [((m .|. modm, k), f i)
-- > | (i, k) <- zip [0..] [1..12]
-- > , (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.
expandWorkspace :: Int -> [WorkspaceId] -> [WorkspaceId]
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]
-- | Create workscreen list from workspace list. Group workspaces to
@@ -95,7 +95,7 @@ viewWorkscreen wscrId = do (WorkscreenStorage c a) <- XS.get
XS.put newWorkscreenStorage
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
shiftWs :: [WorkspaceId] -> [WorkspaceId]