aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDon Stewart <dons@cse.unsw.edu.au>2007-03-07 06:01:39 +0100
committerDon Stewart <dons@cse.unsw.edu.au>2007-03-07 06:01:39 +0100
commitbdc9bd2f6960546f1f80e70d6efca9eb2c4dac14 (patch)
treed663d68bcd6376fb8a19459662021389382f5738
parentb29a91dc7028d3593eb8b05441f8ef1d5bf7a6e0 (diff)
downloadxmonad-bdc9bd2f6960546f1f80e70d6efca9eb2c4dac14.tar.gz
xmonad-bdc9bd2f6960546f1f80e70d6efca9eb2c4dac14.tar.xz
xmonad-bdc9bd2f6960546f1f80e70d6efca9eb2c4dac14.zip
just use [Window]
darcs-hash:20070307050139-9c5c1-a67691477173216dfcfbaf9bf7fea814160586e2.gz
Diffstat (limited to '')
-rw-r--r--Main.hs29
-rw-r--r--W.hs15
2 files changed, 21 insertions, 23 deletions
diff --git a/Main.hs b/Main.hs
index 96493fb..bf5562c 100644
--- a/Main.hs
+++ b/Main.hs
@@ -16,9 +16,6 @@
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 System.IO
@@ -44,7 +41,7 @@ main = do
{ display = dpy
, screenWidth = displayWidth dpy (defaultScreen dpy)
, screenHeight = displayHeight dpy (defaultScreen dpy)
- , windows = Seq.empty
+ , windows = []
}
return ()
@@ -78,7 +75,7 @@ handler :: Event -> W ()
handler (MapRequestEvent {window = w}) = manage w
handler (DestroyWindowEvent {window = w}) = do
- modifyWindows (Seq.fromList . filter (/= w) . Fold.toList)
+ modifyWindows (filter (/= w))
refresh
handler (KeyEvent {event_type = t, state = mod, keycode = code})
@@ -96,11 +93,11 @@ handler _ = return ()
--
switch :: W ()
switch = do
- ws' <- getWindows
- case viewl ws' of
- EmptyL -> return ()
- (w :< ws) -> do
- setWindows (ws |> w)
+ ws <- getWindows
+ case ws of
+ [] -> return ()
+ (x:xs) -> do
+ setWindows (xs++[x]) -- snoc. polish this.
refresh
--
@@ -140,9 +137,9 @@ manage w = do
trace "manage"
d <- getDisplay
ws <- getWindows
- when (Fold.notElem w ws) $ do
+ when (w `notElem` ws) $ do
trace "modifying"
- modifyWindows (w <|)
+ modifyWindows (w :)
io $ mapWindow d w
refresh
@@ -151,10 +148,10 @@ manage w = do
--
refresh :: W ()
refresh = do
- v <- getWindows
- case viewl v of
- EmptyL -> return ()
- (w :< _) -> do
+ ws <- getWindows
+ case ws of
+ [] -> return ()
+ (w:_) -> do
d <- getDisplay
sw <- getScreenWidth
sh <- getScreenHeight
diff --git a/W.hs b/W.hs
index 016baaa..5bacfea 100644
--- a/W.hs
+++ b/W.hs
@@ -16,10 +16,9 @@
module W where
-import Data.Sequence
-import Control.Monad.State
-import System.IO (hFlush, hPutStrLn, stderr)
+import System.IO
import Graphics.X11.Xlib
+import Control.Monad.State
--
-- | WState, the window manager state.
@@ -29,9 +28,11 @@ data WState = WState
{ display :: Display
, screenWidth :: !Int
, screenHeight :: !Int
- , windows :: Seq Window
+ , windows :: Windows
}
+type Windows = [Window]
+
-- | The W monad, a StateT transformer over IO encapuslating the window
-- manager state
--
@@ -85,7 +86,7 @@ getDisplay :: W Display
getDisplay = W (gets display)
-- | Return the current windows
-getWindows :: W (Seq Window)
+getWindows :: W Windows
getWindows = W (gets windows)
-- | Return the screen width
@@ -97,9 +98,9 @@ getScreenHeight :: W Int
getScreenHeight = W (gets screenHeight)
-- | Set the current window list
-setWindows :: Seq Window -> W ()
+setWindows ::Windows -> W ()
setWindows x = W (modify (\s -> s {windows = x}))
-- | Modify the current window list
-modifyWindows :: (Seq Window -> Seq Window) -> W ()
+modifyWindows :: (Windows -> Windows) -> W ()
modifyWindows f = W (modify (\s -> s {windows = f (windows s)}))