mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
just use [Window]
This commit is contained in:
parent
cc947aa5ff
commit
6dedae651f
29
Main.hs
29
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
|
||||
|
15
W.hs
15
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)}))
|
||||
|
Loading…
x
Reference in New Issue
Block a user