derive MonadState, removes most accessors

This commit is contained in:
Don Stewart 2007-03-07 06:15:32 +00:00
parent 96184564d6
commit bea5592b85
2 changed files with 13 additions and 33 deletions

20
Main.hs
View File

@ -78,23 +78,23 @@ handle :: Event -> W ()
handle (MapRequestEvent {window = w}) = manage w
handle (DestroyWindowEvent {window = w}) = do
ws <- getWindows
ws <- gets windows
when (elem w ws) (unmanage w)
handle (UnmapEvent {window = w}) = do
ws <- getWindows
ws <- gets windows
when (elem w ws) (unmanage w)
handle (KeyEvent {event_type = t, state = mod, keycode = code})
| t == keyPress = do
dpy <- getDisplay
dpy <- gets display
sym <- io $ keycodeToKeysym dpy code 0
case filter (\(mod', sym', _) -> mod == mod' && sym == sym') keys of
[] -> return ()
((_, _, act):_) -> act
handle e@(ConfigureRequestEvent {}) = do
dpy <- getDisplay
dpy <- gets display
io $ configureWindow dpy (window e) (value_mask e) $
WindowChanges
{ wcX = x e
@ -121,7 +121,7 @@ withWindows f = do
-- | Run an action on the currently focused window
withCurrent :: (Window -> W ()) -> W ()
withCurrent f = do
ws <- getWindows
ws <- gets windows
case ws of
[] -> return ()
(w:_) -> f w
@ -132,9 +132,9 @@ withCurrent f = do
--
refresh :: W ()
refresh = withCurrent $ \w -> do
d <- getDisplay
sw <- getScreenWidth
sh <- getScreenHeight
d <- gets display
sw <- gets screenWidth
sh <- gets screenHeight
io $ do moveResizeWindow d w 0 0 (fromIntegral sw) (fromIntegral sh)
raiseWindow d w
@ -144,7 +144,7 @@ refresh = withCurrent $ \w -> do
manage :: Window -> W ()
manage w = do
trace "manage"
d <- getDisplay
d <- gets display
withWindows $ \ws -> if w `elem` ws then ws else w:ws -- a set
io $ mapWindow d w
@ -153,7 +153,7 @@ manage w = do
--
unmanage :: Window -> W ()
unmanage w = do
dpy <- getDisplay
dpy <- gets display
io $ grabServer dpy
modifyWindows (filter (/= w))
io $ sync dpy False

24
W.hs
View File

@ -34,7 +34,7 @@ type Windows = [Window]
-- | The W monad, a StateT transformer over IO encapuslating the window
-- manager state
newtype W a = W { unW :: StateT WState IO a }
deriving (Functor, Monad, MonadIO)
deriving (Functor, Monad, MonadIO, MonadState WState)
-- | Run the W monad, given a chunk of W monad code, and an initial state
-- Return the result, and final state
@ -59,29 +59,9 @@ trace msg = io $ do
-- ---------------------------------------------------------------------
-- Getting at the window manager state
-- | Return the current dispaly
getDisplay :: W Display
getDisplay = W (gets display)
-- | Return the current windows
getWindows :: W Windows
getWindows = W (gets windows)
-- | Return the screen width
getScreenWidth :: W Int
getScreenWidth = W (gets screenWidth)
-- | Return the screen height
getScreenHeight :: W Int
getScreenHeight = W (gets screenHeight)
-- | Set the current window list
setWindows ::Windows -> W ()
setWindows x = W (modify (\s -> s {windows = x}))
-- | Modify the current window list
modifyWindows :: (Windows -> Windows) -> W ()
modifyWindows f = W (modify (\s -> s {windows = f (windows s)}))
modifyWindows f = modify $ \s -> s {windows = f (windows s)}
-- ---------------------------------------------------------------------
-- Generic utilities