
On Sat, Apr 4, 2009 at 10:17 PM, Ismael Carnales
Breaking gwern's suggestion this is my second mail today :)
The way to implement some of my suggestions?
* Clean XMonadContrib of duped functionality modules * Reviews XMonadContrib in search of dupped/common-used code * Move this code to another contrib module, and maybe implement a better interface over it * Write good docs about the new module, it will be the base from new modules to come * Maintain this module in partial-stable situation (limitting commits) * Move some functionality of this module to core
With these steps we can assure less breakage fom updating contribs, and that will be more easy to write new modules because there's a common codebase written and approved by core devels.
bye!
These are all good suggestions, but obviously they need to made more specific. Here's one concrete suggestion. In Ubuntu/Debian, there's a package 'similarity-tester'. Install it and then do 'sim_text -d `find XMonadContrib/XMonad`' (changing path as appropriate). This identifies a number of repeated textual patterns. Here're a few: XMonad/Layout/WindowNavigation.hs: line 149-154 XMonad/Config/Droundy.hs: line 174-179 < focusWindowHere s < | Just w == W.peek (windowset s) = s < | has w $ W.stack $ W.workspace $ W.current $ windowset s = < s { windowset = until ((Just w ==) . W.peek) < W.focusUp $ windowset s } < | otherwise = s ---
where copyAndFocus s | Just w == W.peek (windowset s) = s | has w $ W.stack $ W.workspace $ W.current $ windowset s = s { windowset = until ((Just w ==) . W.peek) W.focusUp $ windowset s } | otherwise =
XMonad/Layout/Combo.hs: line 80-84 XMonad/Layout/Combo.hs: line 85-89 < where arrange [] = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage ReleaseResources) < l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage ReleaseResources) < super' <- maybe super id `fmap` < handleMessage super (SomeMessage ReleaseResources) < return ([], Just $ C2 [] [] super' l1' l2') ---
arrange [w] = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage ReleaseResources) l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage ReleaseResources) super' <- maybe super id `fmap` handleMessage super (SomeMessage ReleaseResources) return ([(w,rinput)], Just $ C2 [w] [w] super' l1' l2')
XMonad/Layout/SimplestFloat.hs: line 59-62 XMonad/Layout/SimpleFloat.hs: line 77-80 < y = max ry $ fi $ wa_y wa < wh = (fi $ wa_width wa) + (bw * 2) < ht = (fi $ wa_height wa) + (bw * 2) < return (w, Rectangle x y wh ht) ---
y = max ny $ fi $ wa_y wa wh = (fi $ wa_width wa) + (bw * 2) ht = (fi $ wa_height wa) + (bw * 2) return (w, Rectangle x y wh ht)
XMonad/Actions/CycleWindows.hs: line 136-140 XMonad/Actions/CycleRecentWS.hs: line 71-75 < let evt = allocaXEvent $ < \p -> do maskEvent d (keyPressMask .|. keyReleaseMask) p < KeyEvent {ev_event_type = t, ev_keycode = c} <- getEvent p < s <- keycodeToKeysym d c 0 < return (t, s) ---
let event = allocaXEvent $ \p -> do maskEvent d (keyPressMask .|. keyReleaseMask) p KeyEvent {ev_event_type = t, ev_keycode = c} <- getEvent p s <- keycodeToKeysym d c 0 return (t, s)
XMonad/Actions/FlexibleResize.hs: line 39-42
XMonad/Actions/FloatKeys.hs: line 111-114
keysMoveResize f move resize w = whenX (isClient w) $ withDisplay $ \d -> do io $ raiseWindow d w wa <- io $ getWindowAttributes d w sh <- io $ getWMNormalHints d w
XMonad/Actions/ConstrainedResize.hs: line 46-49
XMonad/Actions/FlexibleResize.hs: line 39-42
mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do io $ raiseWindow d w wa <- io $ getWindowAttributes d w sh <- io $ getWMNormalHints d w
XMonad/Actions/FloatKeys.hs: line 43-46
XMonad/Actions/FloatKeys.hs: line 61-64
keysMoveWindowTo (x,y) (gx, gy) w = whenX (isClient w) $ withDisplay $ \d -> do io $ raiseWindow d w wa <- io $ getWindowAttributes d w io $ moveWindow d w (x - round (gx * fromIntegral (wa_width wa)))
XMonad/Layout/ThreeColumnsMiddle.hs: line 68-70
XMonad/Layout/ThreeColumns.hs: line 58-60
<-- | tile3. Compute window positions using 3 panes
-- | tile3. Compute window positions using 3 panes
tile3 :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
tile3 f r nmaster n XMonad/Layout/ThreeColumnsMiddle.hs: line 78-81
XMonad/Layout/ThreeColumns.hs: line 63-66
< | otherwise = splitVertically nmaster r1 ++ splitVertically nleft r2 ++ splitVertically nright r3
< where (r1, r2, r3) = split3HorizontallyBy f r
< (s1, s2) = splitHorizontallyBy f r
< nslave = (n - nmaster)
--- | otherwise = splitVertically nmaster r1 ++ splitVertically nmid r2 ++ splitVertically nright r3
where (r1, r2, r3) = split3HorizontallyBy f r
(s1, s2) = splitHorizontallyBy f r
nslave = (n - nmaster) XMonad/Prompt/Workspace.hs: line 48-49
XMonad/Prompt/Layout.hs: line 55-56
mkCompl :: [String] -> String -> IO [String]
mkCompl l s = return $ filter (\x -> take (length s) x == s) l Looks like more than a few authors have enjoyed some copy-pasta! This, along with hlint warnings, would be good for new people to work on. (hint hint)
--
gwern