[Xmonad] darcs patch: Main.hs: get rid off non-standard patter...
(and 4 more)
Donald Bruce Stewart
dons at cse.unsw.edu.au
Wed Jun 20 23:37:44 EDT 2007
joachim.fasting:
> Tue Jun 19 00:25:30 CEST 2007 joachim.fasting at gmail.com
> * Main.hs: get rid off non-standard pattern guards.
> Use nested case statements when creating the winset binding.
> Looks _really_ ugly, compared to the original, and adds 3 loc.
>
> Tue Jun 19 05:43:42 CEST 2007 joachim.fasting at gmail.com
> * Xmonad.whenX: flip instead of lambda abstraction.
>
> Wed Jun 20 17:35:41 CEST 2007 joachim.fasting at gmail.com
> * Operations.hs: redundant parens.
>
> Wed Jun 20 18:59:51 CEST 2007 joachim.fasting at gmail.com
> * Remove use of ';' to circumvent layout rules.
> This adds about 3 loc, but using ';' is cheating anyways.
>
> Wed Jun 20 19:08:33 CEST 2007 joachim.fasting at gmail.com
> * XMonad.hs: minor cosmetic code tweaks.
Content-Description: A darcs patch for your repository!
>
> New patches:
>
> [Main.hs: get rid off non-standard pattern guards.
> joachim.fasting at gmail.com**20070618222530
> Use nested case statements when creating the winset binding.
> Looks _really_ ugly, compared to the original, and adds 3 loc.
> ] {
> hunk ./Main.hs 53
> - let winset | ("--resume" : s : _) <- args
> - , [(x, "")] <- reads s = x
> - | otherwise = new [0..fromIntegral workspaces-1] (fromIntegral $ length xinesc)
> + let defaultWinset = new [0..fromIntegral workspaces-1] (fromIntegral $ length xinesc)
> + winset = case args of
> + ("--resume" : s : _) -> case reads s of
> + [(x, [])] -> x
> + _ -> defaultWinset
> + _ -> defaultWinset
> }
Explained why we'll not apply this in previous mail.
>
> [Xmonad.whenX: flip instead of lambda abstraction.
> joachim.fasting at gmail.com**20070619034342] {
> hunk ./XMonad.hs 195
> -whenX a f = a >>= \b -> when b f
> +whenX a f = a >>= flip when f
> }
Well, maybe.
>
> [Operations.hs: redundant parens.
> joachim.fasting at gmail.com**20070620153541] {
> hunk ./Operations.hs 102
> - let n = fromIntegral $ W.screen (W.current ws)
> + let n = fromIntegral . W.screen $ W.current ws
Ok. good.
> hunk ./Operations.hs 146
> - let n = W.tag (W.workspace w)
> + let n = W.tag $ W.workspace w
> }
Rule of thumb is to use () for single application. Its not a crucial
issue though.
>
> [Remove use of ';' to circumvent layout rules.
> joachim.fasting at gmail.com**20070620165951
> This adds about 3 loc, but using ';' is cheating anyways.
> ] {
> hunk ./Main.hs 60
> - safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x,xs)
> + safeLayouts = case defaultLayouts of
> + [] -> (full, [])
> + (x:xs) -> (x,xs)
> hunk ./Operations.hs 115
> - wmdelt <- atom_WM_DELETE_WINDOW ; wmprot <- atom_WM_PROTOCOLS
> -
> + wmdelt <- atom_WM_DELETE_WINDOW
> + wmprot <- atom_WM_PROTOCOLS
> }
No big reason to change these.
>
> [XMonad.hs: minor cosmetic code tweaks.
> joachim.fasting at gmail.com**20070620170833] {
> hunk ./XMonad.hs 86
> - \e -> (do hPutStrLn stderr (show e); runStateT (runReaderT errcase c) st))
> + \e -> hPutStrLn stderr (show e) >> runStateT (runReaderT errcase c) st)
I prefer do notation here.
> hunk ./XMonad.hs 164
> -catchIO f = liftIO (f `catch` \e -> do hPutStrLn stderr (show e); hFlush stderr)
> +catchIO f = liftIO (f `catch` \e -> hPutStrLn stderr (show e) >> hFlush stderr)
; seems fine.
> hunk ./XMonad.hs 185
> - prog <- maybe (io $ getProgName) return mprog
> + prog <- maybe (io getProgName) return mprog
Better, thanks.
> hunk ./XMonad.hs 207
> -trace msg = io $! do hPutStrLn stderr msg; hFlush stderr
> +trace msg = io $! (hPutStrLn stderr msg >> hFlush stderr)
The use of >> complicates this.
More information about the Xmonad
mailing list