hide existential Layout (mostly) from user API.

This commit is contained in:
David Roundy
2007-11-11 00:30:55 +00:00
parent 11711e1a46
commit c8473e3ae9
3 changed files with 12 additions and 11 deletions

View File

@@ -173,7 +173,7 @@ terminal = "xterm"
-- --
-- (The comment formatting character is used when generating the manpage) -- (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 $ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
-- launching and killing programs -- launching and killing programs
[ ((modMask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) -- %! Launch terminal [ ((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 -- | 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 $ mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
-- mod-button1 %! Set the window to floating mode and move by dragging -- mod-button1 %! Set the window to floating mode and move by dragging
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w)) [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
@@ -250,12 +250,11 @@ mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
-- % Extension-provided definitions -- % Extension-provided definitions
-- | And, finally, the default set of configuration values itself -- | And, finally, the default set of configuration values itself
defaultConfig :: XConfig
defaultConfig = XConfig defaultConfig = XConfig
{ XMonad.borderWidth = borderWidth { XMonad.borderWidth = borderWidth
, XMonad.workspaces = workspaces , XMonad.workspaces = workspaces
, XMonad.defaultGaps = defaultGaps , XMonad.defaultGaps = defaultGaps
, XMonad.layoutHook = Layout layout , XMonad.layoutHook = layout
, XMonad.terminal = terminal , XMonad.terminal = terminal
, XMonad.normalBorderColor = normalBorderColor , XMonad.normalBorderColor = normalBorderColor
, XMonad.focusedBorderColor = focusedBorderColor , XMonad.focusedBorderColor = focusedBorderColor

View File

@@ -51,7 +51,7 @@ data XState = XState
data XConf = XConf data XConf = XConf
{ display :: Display -- ^ the X11 display { display :: Display -- ^ the X11 display
, config :: !XConfig -- ^ initial user configuration , config :: !(XConfig Layout) -- ^ initial user configuration
, theRoot :: !Window -- ^ the root window , theRoot :: !Window -- ^ the root window
, normalBorder :: !Pixel -- ^ border color of unfocused windows , normalBorder :: !Pixel -- ^ border color of unfocused windows
, focusedBorder :: !Pixel -- ^ border color of the focused window , focusedBorder :: !Pixel -- ^ border color of the focused window
@@ -62,18 +62,18 @@ data XConf = XConf
} }
-- todo, better name -- todo, better name
data XConfig = XConfig data XConfig l = XConfig
{ normalBorderColor :: !String { normalBorderColor :: !String
, focusedBorderColor :: !String , focusedBorderColor :: !String
, terminal :: !String , terminal :: !String
, layoutHook :: !(Layout Window) , layoutHook :: !(l Window)
, manageHook :: Window -> X (WindowSet -> WindowSet) , manageHook :: Window -> X (WindowSet -> WindowSet)
, workspaces :: [String] , workspaces :: [String]
, defaultGaps :: [(Int,Int,Int,Int)] , defaultGaps :: [(Int,Int,Int,Int)]
, numlockMask :: !KeyMask , numlockMask :: !KeyMask
, modMask :: !KeyMask , modMask :: !KeyMask
, keys :: XConfig -> M.Map (ButtonMask,KeySym) (X ()) , keys :: XConfig Layout -> M.Map (ButtonMask,KeySym) (X ())
, mouseBindings :: XConfig -> M.Map (ButtonMask, Button) (Window -> X ()) , mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
, borderWidth :: !Dimension , borderWidth :: !Dimension
, logHook :: X () , logHook :: X ()
} }

View File

@@ -38,8 +38,10 @@ import System.IO
-- | -- |
-- The main entry point -- The main entry point
-- --
xmonad :: XConfig -> IO () xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
xmonad xmc = do xmonad initxmc = do
-- First, wrap the layout in an existential, to keep things pretty:
let xmc = initxmc { layoutHook = Layout $ layoutHook initxmc }
dpy <- openDisplay "" dpy <- openDisplay ""
let dflt = defaultScreen dpy let dflt = defaultScreen dpy