[xmonad] Haskell question: avoiding code duplication
adam vogt
vogt.adam at gmail.com
Sat Feb 2 19:41:29 CET 2013
On Sat, Feb 2, 2013 at 1:08 PM, Peter Jones <mlists at pmade.com> wrote:
> I've been working on a few customizations to xmonad but as I play with
> Haskell I keep seeing a pattern of duplication in my code that I don't
> know how to resolve. Here's an example:
>
> -- | Enables 'focusFollowsMouse' for tiled windows only. For this to
> -- work you need to turn off 'focusFollowsMouse' in your configuration
> -- and then add this function to your 'handleEventHook'.
> focusFollowsTiledOnly :: Event -> X All
> focusFollowsTiledOnly e@(CrossingEvent {ev_window = w, ev_event_type = t})
> | isNormalEnter = whenX bothTiled (focus w) >> continueHooks
> where isNormalEnter = t == enterNotify && ev_mode e == notifyNormal
> bothTiled = (&&) <$> notFloating w <*> currentIsTiled
> currentIsTiled = currentWindow >>= maybe (return True) notFloating
> currentWindow = gets $ W.peek . windowset
> notFloating w' = gets $ not . M.member w' . W.floating . windowset
> continueHooks = return . mempty $ True
> focusFollowsTiledOnly _ = return . mempty $ True
>
>
> The last two lines demonstrate the pattern I've been seeing. The only
> way I know how to remove this duplication is to move it out into a
> top-level function. Is that correct?
Hi Peter,
Maybe you'll like this version below better. You can use mempty
instead of 'return . mempty $ True'. The latter is a bit confusing
since the True doesn't end up in value, since there's a "instance
Monoid b => Monoid (a -> b)" whose mempty ignores the argument `a'.
import qualified XMonad.StackSet as W
import XMonad
import Data.Monoid
import Data.Map as M
import Control.Applicative
focusFollowsTiledOnly :: Event -> X All
focusFollowsTiledOnly e
| CrossingEvent {ev_window = w, ev_event_type = t} <- e,
let isNormalEnter = t == enterNotify && ev_mode e == notifyNormal
bothTiled = notFloating w <&&> currentIsTiled
currentIsTiled = currentWindow >>= maybe (return True) notFloating
currentWindow = gets $ W.peek . windowset
notFloating w' = gets $ not . M.member w' . W.floating . windowset,
isNormalEnter = whenX bothTiled (focus w) >> mempty
| otherwise = mempty
--
Adam
More information about the xmonad
mailing list