summaryrefslogtreecommitdiffstats
path: root/XMonad/Core.hs
diff options
context:
space:
mode:
authorDaniel Schoepe <daniel.schoepe@gmail.com>2009-11-06 12:50:50 +0100
committerDaniel Schoepe <daniel.schoepe@gmail.com>2009-11-06 12:50:50 +0100
commit9e65e39791460a438c759596768d65f6af9e05d7 (patch)
tree2a0d6f18800103fd8dd655e89fa3308e4314d5a5 /XMonad/Core.hs
parent127096c17db48c14c07df9200dcbda59653e5e40 (diff)
downloadmetatile-9e65e39791460a438c759596768d65f6af9e05d7.tar
metatile-9e65e39791460a438c759596768d65f6af9e05d7.zip
Support for extensible state in contrib modules.
Ignore-this: d04ee1989313ed5710c94f9d7fda3f2a darcs-hash:20091106115050-7f603-c88ce5e468856afd9e4d458ed3b0a2cfa39e63b3
Diffstat (limited to 'XMonad/Core.hs')
-rw-r--r--XMonad/Core.hs46
1 files changed, 39 insertions, 7 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index 1b7b70a..23394f6 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -24,6 +24,7 @@ module XMonad.Core (
XConf(..), XConfig(..), LayoutClass(..),
Layout(..), readsLayout, Typeable, Message,
SomeMessage(..), fromMessage, LayoutMessages(..),
+ StateExtension(..), ExtensionClass(..),
runX, catchX, userCode, userCodeDef, io, catchIO, installSignalHandlers, uninstallSignalHandlers,
withDisplay, withWindowSet, isRoot, runOnWorkspaces,
getAtom, spawn, spawnPID, getXMonadDir, recompile, trace, whenJust, whenX,
@@ -51,20 +52,24 @@ import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras (Event)
import Data.Typeable
import Data.List ((\\))
-import Data.Maybe (isJust)
+import Data.Maybe (isJust,fromMaybe)
import Data.Monoid
-import Data.Maybe (fromMaybe)
import qualified Data.Map as M
import qualified Data.Set as S
-- | XState, the (mutable) window manager state.
data XState = XState
- { windowset :: !WindowSet -- ^ workspace list
- , mapped :: !(S.Set Window) -- ^ the Set of mapped windows
- , waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
- , dragging :: !(Maybe (Position -> Position -> X (), X ())) }
-
+ { windowset :: !WindowSet -- ^ workspace list
+ , mapped :: !(S.Set Window) -- ^ the Set of mapped windows
+ , waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
+ , dragging :: !(Maybe (Position -> Position -> X (), X ()))
+ , extensibleState :: !(M.Map String (Either String StateExtension))
+ -- ^ stores custom state information.
+ --
+ -- The module XMonad.Utils.ExtensibleState in xmonad-contrib
+ -- provides additional information and a simple interface for using this.
+ }
-- | XConf, the (read-only) window manager configuration.
data XConf = XConf
{ display :: Display -- ^ the X11 display
@@ -344,6 +349,33 @@ data LayoutMessages = Hide -- ^ sent when a layout becomes non-visi
instance Message LayoutMessages
-- ---------------------------------------------------------------------
+-- Extensible state
+--
+
+-- | Every module must make the data it wants to store
+-- an instance of this class.
+--
+-- Minimal complete definition: initialValue
+class Typeable a => ExtensionClass a where
+ -- | Defines an initial value for the state extension
+ initialValue :: a
+ -- | Specifies whether the state extension should be
+ -- persistent. Setting this method to 'PersistentExtension'
+ -- will make the stored data survive restarts, but
+ -- requires a to be an instance of Read and Show.
+ --
+ -- It defaults to 'StateExtension', i.e. no persistence.
+ extensionType :: a -> StateExtension
+ extensionType = StateExtension
+
+-- | Existential type to store a state extension.
+data StateExtension =
+ forall a. ExtensionClass a => StateExtension a
+ -- ^ Non-persistent state extension
+ | forall a. (Read a, Show a, ExtensionClass a) => PersistentExtension a
+ -- ^ Persistent extension
+
+-- ---------------------------------------------------------------------
-- | General utilities
--
-- Lift an 'IO' action into the 'X' monad