aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks/ScreenCorners.hs
blob: 747581167c3f86f8d728a7d59c8073ed643c4040 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Hooks.ScreenCorners
-- Copyright   :  (c) 2009 Nils Schweinsberg
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Nils Schweinsberg <mail@n-sch.de>
-- Stability   :  unstable
-- Portability :  unportable
--
-- Run @X ()@ actions by touching the edge of your screen the your mouse.
--
-----------------------------------------------------------------------------

module XMonad.Hooks.ScreenCorners
    (
    -- * Usage
    -- $usage
    -- * Event hook
      screenCornerEventHook
    , ScreenCorner (..)

    -- * X11 input methods
    , defaultEventInput
    , adjustEventInput
    ) where

import Data.Monoid
import Foreign.C.Types

import XMonad
import XMonad.Actions.UpdateFocus (adjustEventInput)

data ScreenCorner = SCUpperLeft
                  | SCUpperRight
                  | SCLowerLeft
                  | SCLowerRight

inCorner :: ScreenCorner -> X () -> Display -> CInt -> CInt -> X ()
inCorner corner xF dpy ix iy = do

    let
        screen = defaultScreen dpy
        xMax   = displayWidth  dpy screen - 1
        yMax   = displayHeight dpy screen - 1
        pos    = case (ix,iy, corner) of
                      (0,0, SCUpperLeft)                           -> Just ()
                      (x,0, SCUpperRight) | x == xMax              -> Just ()
                      (0,y, SCLowerLeft)  | y == yMax              -> Just ()
                      (x,y, SCLowerRight) | x == xMax && y == yMax -> Just ()
                      _                                            -> Nothing

    case pos of
         Just _ -> do
             -- Ignore any MotionEvents
             defaultEventInput
             -- Run our X ()
             xF
             -- Handle MotionEvents again
             adjustEventInput

         _ -> return ()

-- | The event hook manager for @ScreenCorners@.
screenCornerEventHook :: Event -> [(ScreenCorner, X ())] -> X All
screenCornerEventHook MotionEvent { ev_event_display = dpy, ev_x = ix, ev_y = iy } lis = do

    mapM_ (\(c,x) -> inCorner c x dpy ix iy) lis
    return $ All True

screenCornerEventHook _ _ = return $ All True


-- | Use the default input methods
defaultEventInput :: X ()
defaultEventInput = withDisplay $ \dpy -> do
    rootw <- asks theRoot
    io $ selectInput dpy rootw $  substructureRedirectMask .|. substructureNotifyMask
                              .|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
                              .|. buttonPressMask


-- $usage
--
-- This extension adds KDE-like screen corners to XMonad. By moving your cursor
-- into one of your screen corners you can trigger an @X ()@ action, for
-- example "XMonad.Actions.GridSelect".gotoSelected or
-- "XMonad.Actions.CycleWS".nextWS etc.
--
-- To use it, import it on top of your @xmonad.hs@:
--
-- > import XMonad.Hooks.ScreenCorners
--
-- Then add @adjustEventInput@ to your startup hook:
--
-- > myStartupHook = do
-- >     ...
-- >     adjustEventInput
--
-- And put your custom ScreenCorners to your event hook:
--
-- > myEventHook e = do
-- >     ...
-- >     screenCornerEventHook e [ (SCUpperRight, goToSelected defaultGSConfig { gs_cellwidth = 200 })
-- >                             , (SCLowerRight, nextWS)
-- >                             , (SCLowerLeft,  prevWS)
-- >                             ]