1
0
mirror of https://github.com/xmonad/xmonad.git synced 2025-08-18 05:13:47 -07:00

Clean up trailing whitespace

This commit is contained in:
Spencer Janssen
2007-10-15 02:23:22 +00:00
parent 0938298f29
commit bd6a52e587
5 changed files with 25 additions and 25 deletions

@@ -66,7 +66,7 @@ modMask = mod1Mask
numlockMask :: KeyMask
numlockMask = mod2Mask
-- | Width of the window border in pixels.
-- | Width of the window border in pixels.
--
borderWidth :: Dimension
borderWidth = 1
@@ -81,7 +81,7 @@ focusedBorderColor = "#ff0000"
-- screen. Anything non-zero here will leave a gap of that many pixels
-- on the given edge, on the that screen. A useful gap at top of screen
-- for a menu bar (e.g. 15)
--
--
-- An example, to set a top gap on monitor 1, and a gap on the bottom of
-- monitor 2, you'd use a list of geometries like so:
--

@@ -9,7 +9,7 @@
-- Portability : not portable, uses mtl, X11, posix
--
-- xmonad, a minimalist, tiling window manager for X11
--
--
-----------------------------------------------------------------------------
module Main where

@@ -7,7 +7,7 @@
-- Module : Operations.hs
-- Copyright : (c) Spencer Janssen 2007
-- License : BSD3-style (see LICENSE)
--
--
-- Maintainer : dons@cse.unsw.edu.au
-- Stability : unstable
-- Portability : not portable, Typeable deriving, mtl, posix
@@ -416,7 +416,7 @@ instance ReadableLayout a => LayoutClass Select a where
--
-- > fullscreen mode
-- > tall mode
--
--
-- The latter algorithms support the following operations:
--
-- > Shrink
@@ -467,15 +467,15 @@ instance LayoutClass l a => LayoutClass (Mirror l) a where
--
-- The screen is divided (currently) into two panes. all clients are
-- then partioned between these two panes. one pane, the `master', by
-- convention has the least number of windows in it (by default, 1).
-- convention has the least number of windows in it (by default, 1).
-- the variable `nmaster' controls how many windows are rendered in the
-- master pane.
-- master pane.
--
-- `delta' specifies the ratio of the screen to resize by.
--
-- 'frac' specifies what proportion of the screen to devote to the
-- master area.
--
--
tile :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
tile f r nmaster n = if n <= nmaster || nmaster == 0
then splitVertically n r

@@ -55,18 +55,18 @@ import qualified Data.Map as M (Map,insert,delete,empty)
-- window on each workspace has focus. The focused window on the current
-- workspace is the one which will take user input. It can be visualised
-- as follows:
--
--
-- > Workspace { 0*} { 1 } { 2 } { 3 } { 4 }
-- >
-- >
-- > Windows [1 [] [3* [6*] []
-- > ,2*] ,4
-- > ,5]
--
--
-- Note that workspaces are indexed from 0, windows are numbered
-- uniquely. A '*' indicates the window on each workspace that has
-- focus, and which workspace is current.
--
-- Zipper
-- Zipper
--
-- We encode all the focus tracking directly in the data structure, with a 'zipper':
--
@@ -77,7 +77,7 @@ import qualified Data.Map as M (Map,insert,delete,empty)
-- The Zipper lets us replace an item deep in a complex data
-- structure, e.g., a tree or a term, without an mutation. The
-- resulting data structure will share as much of its components with
-- the old structure as possible.
-- the old structure as possible.
--
-- Oleg Kiselyov, 27 Apr 2005, haskell\@, "Zipper as a delimited continuation"
--
@@ -94,7 +94,7 @@ import qualified Data.Map as M (Map,insert,delete,empty)
-- Another good reference is:
--
-- The Zipper, Haskell wikibook
--
--
-- Xinerama support:
--
-- Xinerama in X11 lets us view multiple virtual workspaces
@@ -112,7 +112,7 @@ import qualified Data.Map as M (Map,insert,delete,empty)
-- 'delete'.
--
-- |
-- |
-- API changes from xmonad 0.1:
-- StackSet constructor arguments changed. StackSet workspace window screen
--
@@ -136,7 +136,7 @@ import qualified Data.Map as M (Map,insert,delete,empty)
--
-- * swapMaster, -- was: promote\/swap
--
-- * member,
-- * member,
--
-- * shift,
--
@@ -146,8 +146,8 @@ import qualified Data.Map as M (Map,insert,delete,empty)
--
------------------------------------------------------------------------
-- |
-- A cursor into a non-empty list of workspaces.
--
-- A cursor into a non-empty list of workspaces.
--
-- We puncture the workspace list, producing a hole in the structure
-- used to track the currently focused workspace. The two other lists
-- that are produced are used to track those workspaces visible as
@@ -223,7 +223,7 @@ new l wids m | not (null wids) && length m <= length wids = StackSet cur visi un
new _ _ _ = abort "non-positive argument to StackSet.new"
-- |
-- /O(w)/. Set focus to the workspace with index \'i\'.
-- /O(w)/. Set focus to the workspace with index \'i\'.
-- If the index is out of range, return the original StackSet.
--
-- Xinerama: If the workspace is not visible on any Xinerama screen, it
@@ -306,7 +306,7 @@ modify' :: (Stack a -> Stack a) -> StackSet i l a s sd -> StackSet i l a s sd
modify' f = modify Nothing (Just . f)
-- |
-- /O(1)/. Extract the focused element of the current stack.
-- /O(1)/. Extract the focused element of the current stack.
-- Return Just that element, or Nothing for an empty stack.
--
peek :: StackSet i l a s sd -> Maybe a
@@ -353,7 +353,7 @@ index = with [] integrate
-- let is = t : r ++ reverse l in take (length is) (dropWhile (/= m) (cycle is))
-- |
-- /O(1), O(w) on the wrapping case/.
-- /O(1), O(w) on the wrapping case/.
--
-- focusUp, focusDown. Move the window focus up or down the stack,
-- wrapping if we reach the end. The wrapping should model a -- 'cycle'
@@ -363,7 +363,7 @@ index = with [] integrate
-- swapUp, swapDown, swap the neighbour in the stack ordering, wrapping
-- if we reach the end. Again the wrapping model should 'cycle' on
-- the current stack.
--
--
focusUp, focusDown, swapUp, swapDown :: StackSet i l a s sd -> StackSet i l a s sd
focusUp = modify' focusUp'
focusDown = modify' (reverseStack . focusUp' . reverseStack)
@@ -383,7 +383,7 @@ reverseStack :: Stack a -> Stack a
reverseStack (Stack t ls rs) = Stack t rs ls
--
-- | /O(1) on current window, O(n) in general/. Focus the window 'w',
-- | /O(1) on current window, O(n) in general/. Focus the window 'w',
-- and set its workspace as current.
--
focusWindow :: (Eq s, Eq a, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
@@ -530,7 +530,7 @@ focusMaster = modify' $ \c -> case c of
Stack _ [] _ -> c
Stack t ls rs -> Stack x [] (xs ++ t : rs) where (x:xs) = reverse ls
--
--
-- ---------------------------------------------------------------------
-- $composite

@@ -209,7 +209,7 @@ runLayout l r = maybe (return ([], Nothing)) (doLayout l r)
-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
-- Simon Marlow, 2006. Use extensible messages to the handleMessage handler.
--
--
-- User-extensible messages must be a member of this class.
--
class Typeable a => Message a