summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-11-11 01:30:55 +0100
committerDavid Roundy <droundy@darcs.net>2007-11-11 01:30:55 +0100
commit791029f1e6b1320754314a36e75485cd44298c3d (patch)
tree01afca187cedba61f602a9f9de81e71353042bf1 /XMonad
parentc87dcd06f344a9bb650aaeaeea200169f343650a (diff)
downloadmetatile-791029f1e6b1320754314a36e75485cd44298c3d.tar
metatile-791029f1e6b1320754314a36e75485cd44298c3d.zip
hide existential Layout (mostly) from user API.
darcs-hash:20071111003055-72aca-77eb2071cd596e0e13746413807f375d199dbe32
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Config.hs7
-rw-r--r--XMonad/Core.hs10
-rw-r--r--XMonad/Main.hs6
3 files changed, 12 insertions, 11 deletions
diff --git a/XMonad/Config.hs b/XMonad/Config.hs
index 1cab6a3..a645207 100644
--- a/XMonad/Config.hs
+++ b/XMonad/Config.hs
@@ -173,7 +173,7 @@ terminal = "xterm"
--
-- (The comment formatting character is used when generating the manpage)
--
-keys :: XConfig -> M.Map (KeyMask, KeySym) (X ())
+keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
-- launching and killing programs
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) -- %! Launch terminal
@@ -234,7 +234,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
-- | Mouse bindings: default actions bound to mouse events
--
-mouseBindings :: XConfig -> M.Map (KeyMask, Button) (Window -> X ())
+mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
-- mod-button1 %! Set the window to floating mode and move by dragging
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
@@ -250,12 +250,11 @@ mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
-- % Extension-provided definitions
-- | And, finally, the default set of configuration values itself
-defaultConfig :: XConfig
defaultConfig = XConfig
{ XMonad.borderWidth = borderWidth
, XMonad.workspaces = workspaces
, XMonad.defaultGaps = defaultGaps
- , XMonad.layoutHook = Layout layout
+ , XMonad.layoutHook = layout
, XMonad.terminal = terminal
, XMonad.normalBorderColor = normalBorderColor
, XMonad.focusedBorderColor = focusedBorderColor
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index 2a6a715..9ef7972 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -51,7 +51,7 @@ data XState = XState
data XConf = XConf
{ display :: Display -- ^ the X11 display
- , config :: !XConfig -- ^ initial user configuration
+ , config :: !(XConfig Layout) -- ^ initial user configuration
, theRoot :: !Window -- ^ the root window
, normalBorder :: !Pixel -- ^ border color of unfocused windows
, focusedBorder :: !Pixel -- ^ border color of the focused window
@@ -62,18 +62,18 @@ data XConf = XConf
}
-- todo, better name
-data XConfig = XConfig
+data XConfig l = XConfig
{ normalBorderColor :: !String
, focusedBorderColor :: !String
, terminal :: !String
- , layoutHook :: !(Layout Window)
+ , layoutHook :: !(l Window)
, manageHook :: Window -> X (WindowSet -> WindowSet)
, workspaces :: [String]
, defaultGaps :: [(Int,Int,Int,Int)]
, numlockMask :: !KeyMask
, modMask :: !KeyMask
- , keys :: XConfig -> M.Map (ButtonMask,KeySym) (X ())
- , mouseBindings :: XConfig -> M.Map (ButtonMask, Button) (Window -> X ())
+ , keys :: XConfig Layout -> M.Map (ButtonMask,KeySym) (X ())
+ , mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
, borderWidth :: !Dimension
, logHook :: X ()
}
diff --git a/XMonad/Main.hs b/XMonad/Main.hs
index c40e45e..5054c79 100644
--- a/XMonad/Main.hs
+++ b/XMonad/Main.hs
@@ -38,8 +38,10 @@ import System.IO
-- |
-- The main entry point
--
-xmonad :: XConfig -> IO ()
-xmonad xmc = do
+xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
+xmonad initxmc = do
+ -- First, wrap the layout in an existential, to keep things pretty:
+ let xmc = initxmc { layoutHook = Layout $ layoutHook initxmc }
dpy <- openDisplay ""
let dflt = defaultScreen dpy