aboutsummaryrefslogtreecommitdiffstats
path: root/Main.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@cse.unsw.edu.au>2007-03-07 04:38:55 +0100
committerDon Stewart <dons@cse.unsw.edu.au>2007-03-07 04:38:55 +0100
commitec48390072857ce86d060ff9d710fb8b317570f3 (patch)
tree11a2250c03d4bc68665109f0670c00e3666b58e2 /Main.hs
parent3c4a8246317d44e48f82dfd6d9ecff6b2e65c787 (diff)
downloadxmonad-ec48390072857ce86d060ff9d710fb8b317570f3.tar.gz
xmonad-ec48390072857ce86d060ff9d710fb8b317570f3.tar.xz
xmonad-ec48390072857ce86d060ff9d710fb8b317570f3.zip
refactoring
darcs-hash:20070307033855-9c5c1-999ba9e7d3cd15a6363e8da777879ed72d0020c6.gz
Diffstat (limited to 'Main.hs')
-rw-r--r--Main.hs28
1 files changed, 16 insertions, 12 deletions
diff --git a/Main.hs b/Main.hs
index 66afef8..16c7cee 100644
--- a/Main.hs
+++ b/Main.hs
@@ -15,16 +15,21 @@
import qualified Data.Map as Map
import Data.Map (Map)
+
import Data.Sequence as Seq
import qualified Data.Foldable as Fold
+
import Data.Bits
-import Control.Monad.State
+
import System.IO
-import Graphics.X11.Xlib
-import Graphics.X11.Xlib.Extras
import System.Process (runCommand)
import System.Exit
+import Graphics.X11.Xlib
+import Graphics.X11.Xlib.Extras
+
+import Control.Monad.State
+
import W
------------------------------------------------------------------------
@@ -65,8 +70,6 @@ loop = do
forever $ do
e <- io $ allocaXEvent $ \ev -> nextEvent dpy ev >> getEvent ev
handler e
- where
- forever a = a >> forever a
--
-- The event handler
@@ -78,13 +81,14 @@ handler (DestroyWindowEvent {window = w}) = do
modifyWindows (Seq.fromList . filter (/= w) . Fold.toList)
refresh
-handler (KeyEvent {event_type = t, state = mod, keycode = code})
- | t == keyPress = do
- dpy <- getDisplay
- sym <- io $ keycodeToKeysym dpy code 0
- case filter (\(mod', sym', _) -> mod == mod' && sym == sym') keys of
- [] -> return ()
- ((_, _, act):_) -> act
+handler (KeyEvent {event_type = t, state = mod, keycode = code})
+ | t == keyPress = do
+ dpy <- getDisplay
+ sym <- io $ keycodeToKeysym dpy code 0
+ case filter (\(mod', sym', _) -> mod == mod' && sym == sym') keys of
+ [] -> return ()
+ ((_, _, act):_) -> act
+
handler _ = return ()
--