aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@cse.unsw.edu.au>2007-03-10 08:01:52 +0100
committerDon Stewart <dons@cse.unsw.edu.au>2007-03-10 08:01:52 +0100
commit44ffcec3db8f778814d98acbb36f304d8bc6b956 (patch)
treea61c2cab41f7445b9c02bdf1e13b662c1a92546c /XMonad.hs
parentdccc5d7f95a3a0f6219edbbd4868fefdf68234d6 (diff)
downloadxmonad-44ffcec3db8f778814d98acbb36f304d8bc6b956.tar.gz
xmonad-44ffcec3db8f778814d98acbb36f304d8bc6b956.tar.xz
xmonad-44ffcec3db8f778814d98acbb36f304d8bc6b956.zip
XMonad
darcs-hash:20070310070152-9c5c1-f78385326379d5ff19cb3db926c5b02117e433ff.gz
Diffstat (limited to '')
-rw-r--r--XMonad.hs (renamed from WMonad.hs)38
1 files changed, 19 insertions, 19 deletions
diff --git a/WMonad.hs b/XMonad.hs
index 4e622c5..77c5a2e 100644
--- a/WMonad.hs
+++ b/XMonad.hs
@@ -1,6 +1,6 @@
-----------------------------------------------------------------------------
-- |
--- Module : WMonad.hs
+-- Module : XMonad.hs
-- Copyright : (c) Spencer Janssen 2007
-- License : BSD3-style (see LICENSE)
--
@@ -10,12 +10,12 @@
--
-----------------------------------------------------------------------------
--
--- The W monad, a state monad transformer over IO, for the window
+-- The X monad, a state monad transformer over IO, for the window
-- manager state, and support routines.
--
-module WMonad (
- W, WorkSpace, WState(..),runW, withDisplay, io, spawn, trace, whenJust
+module XMonad (
+ X, WorkSpace, XState(..),runX, withDisplay, io, spawn, trace, whenJust
) where
import StackSet (StackSet)
@@ -25,9 +25,9 @@ import System.IO
import System.Process (runCommand)
import Graphics.X11.Xlib (Display,Window)
--- | WState, the window manager state.
+-- | XState, the window manager state.
-- Just the display, width, height and a window list
-data WState = WState
+data XState = XState
{ display :: Display
, screenWidth :: {-# UNPACK #-} !Int
, screenHeight :: {-# UNPACK #-} !Int
@@ -36,36 +36,36 @@ data WState = WState
type WorkSpace = StackSet Window
--- | The W monad, a StateT transformer over IO encapuslating the window
+-- | The X monad, a StateT transformer over IO encapuslating the window
-- manager state
-newtype W a = W (StateT WState IO a)
- deriving (Functor, Monad, MonadIO, MonadState WState)
+newtype X a = X (StateT XState IO a)
+ deriving (Functor, Monad, MonadIO, MonadState XState)
--- | Run the W monad, given a chunk of W monad code, and an initial state
+-- | Run the X monad, given a chunk of X monad code, and an initial state
-- Return the result, and final state
-runW :: WState -> W a -> IO ()
-runW st (W a) = runStateT a st >> return ()
+runX :: XState -> X a -> IO ()
+runX st (X a) = runStateT a st >> return ()
-- | Run a monad action with the current display settings
-withDisplay :: (Display -> W ()) -> W ()
+withDisplay :: (Display -> X ()) -> X ()
withDisplay f = gets display >>= f
------------------------------------------------------------------------
--- | Lift an IO action into the W monad
-io :: IO a -> W a
+-- | Lift an IO action into the X monad
+io :: IO a -> X a
io = liftIO
{-# INLINE io #-}
-- | spawn. Launch an external application
-spawn :: String -> W ()
+spawn :: String -> X ()
spawn x = io (runCommand x) >> return ()
-- | Run a side effecting action with the current workspace. Like 'when' but
-whenJust :: Maybe a -> (a -> W ()) -> W ()
+whenJust :: Maybe a -> (a -> X ()) -> X ()
whenJust mg f = maybe (return ()) f mg
--- | A 'trace' for the W monad. Logs a string to stderr. The result may
+-- | A 'trace' for the X monad. Logs a string to stderr. The result may
-- be found in your .xsession-errors file
-trace :: String -> W ()
+trace :: String -> X ()
trace msg = io $! do hPutStrLn stderr msg; hFlush stderr