diff options
author | Don Stewart <dons@cse.unsw.edu.au> | 2007-03-07 04:33:07 +0100 |
---|---|---|
committer | Don Stewart <dons@cse.unsw.edu.au> | 2007-03-07 04:33:07 +0100 |
commit | 3c4a8246317d44e48f82dfd6d9ecff6b2e65c787 (patch) | |
tree | 57acc8c643e155fc9d36e409c3723912308b2141 /Wm.hs | |
parent | 9e916d17e85b338904cddb6a71b773d93439ac20 (diff) | |
download | xmonad-3c4a8246317d44e48f82dfd6d9ecff6b2e65c787.tar.gz xmonad-3c4a8246317d44e48f82dfd6d9ecff6b2e65c787.tar.xz xmonad-3c4a8246317d44e48f82dfd6d9ecff6b2e65c787.zip |
Wm -> W, all good monads have single capital letter names. comment the W.hs file
darcs-hash:20070307033307-9c5c1-2e7136f75725d311a8d19838b46e7fa89c3e4dc9.gz
Diffstat (limited to '')
-rw-r--r-- | Wm.hs | 70 |
1 files changed, 0 insertions, 70 deletions
@@ -1,70 +0,0 @@ ------------------------------------------------------------------------------ --- | --- Module : Wm.hs --- Copyright : (c) Spencer Janssen 2007 --- License : BSD3-style (see LICENSE) --- --- Maintainer : sjanssen@cse.unl.edu --- Stability : unstable --- Portability : not portable, uses cunning newtype deriving --- ------------------------------------------------------------------------------ --- --- The Wm monad, a state monad transformer over IO, for the window manager state. --- - -module Wm where - -import Data.Sequence -import Control.Monad.State -import System.IO (hFlush, hPutStrLn, stderr) -import Graphics.X11.Xlib - -data WmState = WmState - { display :: Display - , screenWidth :: !Int - , screenHeight :: !Int - , windows :: Seq Window - } - -newtype Wm a = Wm (StateT WmState IO a) - deriving (Monad, MonadIO{-, MonadState WmState-}) - -runWm :: Wm a -> WmState -> IO (a, WmState) -runWm (Wm m) = runStateT m - --- --- | Lift an IO action into the Wm monad --- -io :: IO a -> Wm a -io = liftIO - --- --- | Lift an IO action into the Wm monad, discarding any result --- -io_ :: IO a -> Wm () -io_ f = liftIO f >> return () - -trace msg = io $ do - hPutStrLn stderr msg - hFlush stderr - -withIO :: (forall b. (a -> IO b) -> IO b) -> (a -> Wm c) -> Wm c -withIO f g = do - s <- Wm get - (y, s') <- io $ f $ \x -> runWm (g x) s - Wm (put s') - return y - -getDisplay = Wm (gets display) - -getWindows = Wm (gets windows) - -getScreenWidth = Wm (gets screenWidth) - -getScreenHeight = Wm (gets screenHeight) - -setWindows x = Wm (modify (\s -> s {windows = x})) - -modifyWindows :: (Seq Window -> Seq Window) -> Wm () -modifyWindows f = Wm (modify (\s -> s {windows = f (windows s)})) |