summaryrefslogtreecommitdiffstats
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
commit10fd9ba251610144fc1a95611a8c003171c60117 (patch)
treea61c2cab41f7445b9c02bdf1e13b662c1a92546c /XMonad.hs
parent4fd3777615fe81f1b140acbe26ee7f0e4af244d2 (diff)
downloadmetatile-10fd9ba251610144fc1a95611a8c003171c60117.tar
metatile-10fd9ba251610144fc1a95611a8c003171c60117.zip
XMonad
darcs-hash:20070310070152-9c5c1-f78385326379d5ff19cb3db926c5b02117e433ff
Diffstat (limited to 'XMonad.hs')
-rw-r--r--XMonad.hs71
1 files changed, 71 insertions, 0 deletions
diff --git a/XMonad.hs b/XMonad.hs
new file mode 100644
index 0000000..77c5a2e
--- /dev/null
+++ b/XMonad.hs
@@ -0,0 +1,71 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.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 X monad, a state monad transformer over IO, for the window
+-- manager state, and support routines.
+--
+
+module XMonad (
+ X, WorkSpace, XState(..),runX, withDisplay, io, spawn, trace, whenJust
+ ) where
+
+import StackSet (StackSet)
+
+import Control.Monad.State
+import System.IO
+import System.Process (runCommand)
+import Graphics.X11.Xlib (Display,Window)
+
+-- | XState, the window manager state.
+-- Just the display, width, height and a window list
+data XState = XState
+ { display :: Display
+ , screenWidth :: {-# UNPACK #-} !Int
+ , screenHeight :: {-# UNPACK #-} !Int
+ , workspace :: {-# UNPACK #-} !WorkSpace -- ^ workspace list
+ }
+
+type WorkSpace = StackSet Window
+
+-- | The X monad, a StateT transformer over IO encapuslating the window
+-- manager state
+newtype X a = X (StateT XState IO a)
+ deriving (Functor, Monad, MonadIO, MonadState XState)
+
+-- | Run the X monad, given a chunk of X monad code, and an initial state
+-- Return the result, and final state
+runX :: XState -> X a -> IO ()
+runX st (X a) = runStateT a st >> return ()
+
+-- | Run a monad action with the current display settings
+withDisplay :: (Display -> X ()) -> X ()
+withDisplay f = gets display >>= f
+
+------------------------------------------------------------------------
+
+-- | Lift an IO action into the X monad
+io :: IO a -> X a
+io = liftIO
+{-# INLINE io #-}
+
+-- | spawn. Launch an external application
+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 -> X ()) -> X ()
+whenJust mg f = maybe (return ()) f mg
+
+-- | A 'trace' for the X monad. Logs a string to stderr. The result may
+-- be found in your .xsession-errors file
+trace :: String -> X ()
+trace msg = io $! do hPutStrLn stderr msg; hFlush stderr