mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
refactoring
This commit is contained in:
parent
0330a354f9
commit
48fe0f45f2
26
Main.hs
26
Main.hs
@ -15,16 +15,21 @@
|
|||||||
|
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
|
|
||||||
import Data.Sequence as Seq
|
import Data.Sequence as Seq
|
||||||
import qualified Data.Foldable as Fold
|
import qualified Data.Foldable as Fold
|
||||||
|
|
||||||
import Data.Bits
|
import Data.Bits
|
||||||
import Control.Monad.State
|
|
||||||
import System.IO
|
import System.IO
|
||||||
import Graphics.X11.Xlib
|
|
||||||
import Graphics.X11.Xlib.Extras
|
|
||||||
import System.Process (runCommand)
|
import System.Process (runCommand)
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
|
||||||
|
import Graphics.X11.Xlib
|
||||||
|
import Graphics.X11.Xlib.Extras
|
||||||
|
|
||||||
|
import Control.Monad.State
|
||||||
|
|
||||||
import W
|
import W
|
||||||
|
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
@ -65,8 +70,6 @@ loop = do
|
|||||||
forever $ do
|
forever $ do
|
||||||
e <- io $ allocaXEvent $ \ev -> nextEvent dpy ev >> getEvent ev
|
e <- io $ allocaXEvent $ \ev -> nextEvent dpy ev >> getEvent ev
|
||||||
handler e
|
handler e
|
||||||
where
|
|
||||||
forever a = a >> forever a
|
|
||||||
|
|
||||||
--
|
--
|
||||||
-- The event handler
|
-- The event handler
|
||||||
@ -79,12 +82,13 @@ handler (DestroyWindowEvent {window = w}) = do
|
|||||||
refresh
|
refresh
|
||||||
|
|
||||||
handler (KeyEvent {event_type = t, state = mod, keycode = code})
|
handler (KeyEvent {event_type = t, state = mod, keycode = code})
|
||||||
| t == keyPress = do
|
| t == keyPress = do
|
||||||
dpy <- getDisplay
|
dpy <- getDisplay
|
||||||
sym <- io $ keycodeToKeysym dpy code 0
|
sym <- io $ keycodeToKeysym dpy code 0
|
||||||
case filter (\(mod', sym', _) -> mod == mod' && sym == sym') keys of
|
case filter (\(mod', sym', _) -> mod == mod' && sym == sym') keys of
|
||||||
[] -> return ()
|
[] -> return ()
|
||||||
((_, _, act):_) -> act
|
((_, _, act):_) -> act
|
||||||
|
|
||||||
handler _ = return ()
|
handler _ = return ()
|
||||||
|
|
||||||
--
|
--
|
||||||
|
9
W.hs
9
W.hs
@ -10,7 +10,8 @@
|
|||||||
--
|
--
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
--
|
--
|
||||||
-- The W monad, a state monad transformer over IO, for the window manager state.
|
-- The W monad, a state monad transformer over IO, for the window
|
||||||
|
-- manager state, and support routines.
|
||||||
--
|
--
|
||||||
|
|
||||||
module W where
|
module W where
|
||||||
@ -70,6 +71,12 @@ trace msg = io $ do
|
|||||||
hPutStrLn stderr msg
|
hPutStrLn stderr msg
|
||||||
hFlush stderr
|
hFlush stderr
|
||||||
|
|
||||||
|
--
|
||||||
|
-- | Run an action forever
|
||||||
|
--
|
||||||
|
forever :: (Monad m) => m a -> m b
|
||||||
|
forever a = a >> forever a
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Getting at the window manager state
|
-- Getting at the window manager state
|
||||||
|
|
||||||
|
Loading…
x
Reference in New Issue
Block a user