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 qualified Data.Map as Map
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
|
|
||||||
import Data.Sequence as Seq
|
|
||||||
import qualified Data.Foldable as Fold
|
|
||||||
|
|
||||||
import Data.Bits
|
import Data.Bits
|
||||||
|
|
||||||
import System.IO
|
import System.IO
|
||||||
@ -44,7 +41,7 @@ main = do
|
|||||||
{ display = dpy
|
{ display = dpy
|
||||||
, screenWidth = displayWidth dpy (defaultScreen dpy)
|
, screenWidth = displayWidth dpy (defaultScreen dpy)
|
||||||
, screenHeight = displayHeight dpy (defaultScreen dpy)
|
, screenHeight = displayHeight dpy (defaultScreen dpy)
|
||||||
, windows = Seq.empty
|
, windows = []
|
||||||
}
|
}
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
@ -78,7 +75,7 @@ handler :: Event -> W ()
|
|||||||
handler (MapRequestEvent {window = w}) = manage w
|
handler (MapRequestEvent {window = w}) = manage w
|
||||||
|
|
||||||
handler (DestroyWindowEvent {window = w}) = do
|
handler (DestroyWindowEvent {window = w}) = do
|
||||||
modifyWindows (Seq.fromList . filter (/= w) . Fold.toList)
|
modifyWindows (filter (/= w))
|
||||||
refresh
|
refresh
|
||||||
|
|
||||||
handler (KeyEvent {event_type = t, state = mod, keycode = code})
|
handler (KeyEvent {event_type = t, state = mod, keycode = code})
|
||||||
@ -96,11 +93,11 @@ handler _ = return ()
|
|||||||
--
|
--
|
||||||
switch :: W ()
|
switch :: W ()
|
||||||
switch = do
|
switch = do
|
||||||
ws' <- getWindows
|
ws <- getWindows
|
||||||
case viewl ws' of
|
case ws of
|
||||||
EmptyL -> return ()
|
[] -> return ()
|
||||||
(w :< ws) -> do
|
(x:xs) -> do
|
||||||
setWindows (ws |> w)
|
setWindows (xs++[x]) -- snoc. polish this.
|
||||||
refresh
|
refresh
|
||||||
|
|
||||||
--
|
--
|
||||||
@ -140,9 +137,9 @@ manage w = do
|
|||||||
trace "manage"
|
trace "manage"
|
||||||
d <- getDisplay
|
d <- getDisplay
|
||||||
ws <- getWindows
|
ws <- getWindows
|
||||||
when (Fold.notElem w ws) $ do
|
when (w `notElem` ws) $ do
|
||||||
trace "modifying"
|
trace "modifying"
|
||||||
modifyWindows (w <|)
|
modifyWindows (w :)
|
||||||
io $ mapWindow d w
|
io $ mapWindow d w
|
||||||
refresh
|
refresh
|
||||||
|
|
||||||
@ -151,10 +148,10 @@ manage w = do
|
|||||||
--
|
--
|
||||||
refresh :: W ()
|
refresh :: W ()
|
||||||
refresh = do
|
refresh = do
|
||||||
v <- getWindows
|
ws <- getWindows
|
||||||
case viewl v of
|
case ws of
|
||||||
EmptyL -> return ()
|
[] -> return ()
|
||||||
(w :< _) -> do
|
(w:_) -> do
|
||||||
d <- getDisplay
|
d <- getDisplay
|
||||||
sw <- getScreenWidth
|
sw <- getScreenWidth
|
||||||
sh <- getScreenHeight
|
sh <- getScreenHeight
|
||||||
|
15
W.hs
15
W.hs
@ -16,10 +16,9 @@
|
|||||||
|
|
||||||
module W where
|
module W where
|
||||||
|
|
||||||
import Data.Sequence
|
import System.IO
|
||||||
import Control.Monad.State
|
|
||||||
import System.IO (hFlush, hPutStrLn, stderr)
|
|
||||||
import Graphics.X11.Xlib
|
import Graphics.X11.Xlib
|
||||||
|
import Control.Monad.State
|
||||||
|
|
||||||
--
|
--
|
||||||
-- | WState, the window manager state.
|
-- | WState, the window manager state.
|
||||||
@ -29,9 +28,11 @@ data WState = WState
|
|||||||
{ display :: Display
|
{ display :: Display
|
||||||
, screenWidth :: !Int
|
, screenWidth :: !Int
|
||||||
, screenHeight :: !Int
|
, screenHeight :: !Int
|
||||||
, windows :: Seq Window
|
, windows :: Windows
|
||||||
}
|
}
|
||||||
|
|
||||||
|
type Windows = [Window]
|
||||||
|
|
||||||
-- | The W monad, a StateT transformer over IO encapuslating the window
|
-- | The W monad, a StateT transformer over IO encapuslating the window
|
||||||
-- manager state
|
-- manager state
|
||||||
--
|
--
|
||||||
@ -85,7 +86,7 @@ getDisplay :: W Display
|
|||||||
getDisplay = W (gets display)
|
getDisplay = W (gets display)
|
||||||
|
|
||||||
-- | Return the current windows
|
-- | Return the current windows
|
||||||
getWindows :: W (Seq Window)
|
getWindows :: W Windows
|
||||||
getWindows = W (gets windows)
|
getWindows = W (gets windows)
|
||||||
|
|
||||||
-- | Return the screen width
|
-- | Return the screen width
|
||||||
@ -97,9 +98,9 @@ getScreenHeight :: W Int
|
|||||||
getScreenHeight = W (gets screenHeight)
|
getScreenHeight = W (gets screenHeight)
|
||||||
|
|
||||||
-- | Set the current window list
|
-- | Set the current window list
|
||||||
setWindows :: Seq Window -> W ()
|
setWindows ::Windows -> W ()
|
||||||
setWindows x = W (modify (\s -> s {windows = x}))
|
setWindows x = W (modify (\s -> s {windows = x}))
|
||||||
|
|
||||||
-- | Modify the current window list
|
-- | 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)}))
|
modifyWindows f = W (modify (\s -> s {windows = f (windows s)}))
|
||||||
|
Loading…
x
Reference in New Issue
Block a user